1
1
mirror of https://github.com/github/semantic.git synced 2024-12-19 12:51:52 +03:00

Define a class of terms that can be analyzed.

This commit is contained in:
Rob Rix 2019-10-18 14:08:50 -04:00
parent 95abbb3ce1
commit 731173fc48
No known key found for this signature in database
GPG Key ID: F188A01508EA1CF7

View File

@ -1,6 +1,8 @@
{-# LANGUAGE GADTs, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE GADTs, KindSignatures, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
module Semantic.Graph
( runGraph
( analysisParsers
, AnalyzeTerm(..)
, runGraph
, runCallGraph
, runImportGraph
, runImportGraphToModules
@ -56,6 +58,7 @@ import Data.Graph
import Data.Graph.ControlFlowVertex (VertexDeclaration)
import Data.Language as Language
import Data.List (isPrefixOf, isSuffixOf)
import qualified Data.Map as Map
import Data.Project
import Data.Text (pack, unpack)
import Language.Haskell.HsColour
@ -95,6 +98,32 @@ instance
, Show1 syntax
) => AnalysisClasses syntax
class
( VertexDeclaration term
, Declarations (term Loc)
, AccessControls (term Loc)
, Ord (term Loc)
, Evaluatable (Base (term Loc))
, FreeVariables (term Loc)
, Recursive (term Loc)
, Show (term Loc)
, HasSpan (term Loc)
) => AnalyzeTerm (term :: * -> *) where
evaluateTerm
:: (term Loc -> Evaluator (term Loc) address value m value)
-> (term Loc -> Evaluator (term Loc) address value m value)
analysisParsers :: Map Language (SomeParser AnalyzeTerm Loc)
analysisParsers = Map.fromList
[ goParser'
, javascriptParser'
, phpParser'
, pythonParserALaCarte'
, rubyParser'
, typescriptParser'
, tsxParser'
]
runGraph :: ( Member Distribute sig
, Member Parse sig
, Member Resolution sig