mirror of
https://github.com/github/semantic.git
synced 2024-12-24 07:25:44 +03:00
🔥 the termInfo parameter from Located.
This commit is contained in:
parent
30b8002394
commit
4c5734452a
@ -56,17 +56,17 @@ style = (defaultStyle vertexName)
|
||||
|
||||
graphingTerms :: forall location term value effects syntax ann a
|
||||
. ( Element Syntax.Identifier syntax
|
||||
, Members '[ Reader (Environment (Located location (Base term ())) value)
|
||||
, Members '[ Reader (Environment (Located location) value)
|
||||
, Reader ModuleInfo
|
||||
, Reader PackageInfo
|
||||
, Resumable (LoadError term)
|
||||
, State (Environment (Located location (Base term ())) value)
|
||||
, State (Environment (Located location) value)
|
||||
, State (ImportGraph term)
|
||||
] effects
|
||||
, term ~ Term (Sum syntax) ann
|
||||
)
|
||||
=> SubtermAlgebra (Base term) term (Evaluator (Located location (Base term ())) term value effects a)
|
||||
-> SubtermAlgebra (Base term) term (Evaluator (Located location (Base term ())) term value effects a)
|
||||
=> SubtermAlgebra (Base term) term (Evaluator (Located location) term value effects a)
|
||||
-> SubtermAlgebra (Base term) term (Evaluator (Located location) term value effects a)
|
||||
graphingTerms recur term@(In _ syntax) = do
|
||||
case projectSum syntax of
|
||||
Just (Syntax.Identifier name) -> do
|
||||
@ -118,12 +118,12 @@ moduleInclusion v = do
|
||||
appendGraph (moduleGraph m `connect` vertex v)
|
||||
|
||||
-- | Add an edge from the passed variable name to the module it originated within.
|
||||
variableDefinition :: ( Member (Reader (Environment (Located location (Base term ())) value)) effects
|
||||
, Member (State (Environment (Located location (Base term ())) value)) effects
|
||||
variableDefinition :: ( Member (Reader (Environment (Located location) value)) effects
|
||||
, Member (State (Environment (Located location) value)) effects
|
||||
, Member (State (ImportGraph term)) effects
|
||||
)
|
||||
=> Name
|
||||
-> Evaluator (Located location (Base term ())) term value effects ()
|
||||
-> Evaluator (Located location) term value effects ()
|
||||
variableDefinition name = do
|
||||
graph <- maybe empty (moduleGraph . locationModule . unAddress) <$> lookupEnv name
|
||||
appendGraph (vertex (Variable (unName name)) `connect` graph)
|
||||
|
@ -8,18 +8,18 @@ import Data.Abstract.Module (ModuleInfo)
|
||||
import Data.Abstract.Package (PackageInfo)
|
||||
import Prologue
|
||||
|
||||
data Located location termInfo = Located { location :: location, locationPackage :: {-# UNPACK #-} !PackageInfo, locationModule :: {-# UNPACK #-} !ModuleInfo }
|
||||
data Located location = Located { location :: location, locationPackage :: {-# UNPACK #-} !PackageInfo, locationModule :: {-# UNPACK #-} !ModuleInfo }
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Location location => Location (Located location termInfo) where
|
||||
type Cell (Located location termInfo) = Cell location
|
||||
instance Location location => Location (Located location) where
|
||||
type Cell (Located location) = Cell location
|
||||
|
||||
instance ( Addressable location effects
|
||||
, Members '[ Reader ModuleInfo
|
||||
, Reader PackageInfo
|
||||
] effects
|
||||
)
|
||||
=> Addressable (Located location termInfo) effects where
|
||||
=> Addressable (Located location) effects where
|
||||
derefCell (Address (Located loc _ _)) = raise . lower . derefCell (Address loc)
|
||||
|
||||
allocLoc name = raise (lower (Located <$> allocLoc name <*> currentPackage <*> currentModule))
|
||||
|
@ -62,22 +62,22 @@ parseModule parser rootDir file = do
|
||||
|
||||
|
||||
importGraphAnalysis :: forall term syntax ann a
|
||||
. Evaluator (Located Precise (Base term ())) term (Value (Located Precise (Base term ())))
|
||||
. Evaluator (Located Precise) term (Value (Located Precise))
|
||||
( State (ImportGraph (Term (Sum syntax) ann))
|
||||
': Resumable (AddressError (Located Precise (Base term ())) (Value (Located Precise (Base term ()))))
|
||||
': Resumable (AddressError (Located Precise) (Value (Located Precise)))
|
||||
': Resumable ResolutionError
|
||||
': Resumable (EvalError (Value (Located Precise (Base term ()))))
|
||||
': Resumable (EvalError (Value (Located Precise)))
|
||||
': State [Name]
|
||||
': Resumable (ValueError (Located Precise (Base term ())) (Value (Located Precise (Base term ()))))
|
||||
': Resumable (Unspecialized (Value (Located Precise (Base term ()))))
|
||||
': Resumable (ValueError (Located Precise) (Value (Located Precise)))
|
||||
': Resumable (Unspecialized (Value (Located Precise)))
|
||||
': Resumable (LoadError term)
|
||||
': EvaluatingEffects (Located Precise (Base term ())) term (Value (Located Precise (Base term ())))) a
|
||||
-> ( Either String -- 'fail' calls
|
||||
( Either (SomeExc (LoadError term)) -- Unhandled LoadErrors
|
||||
( ( a -- the result value
|
||||
, ImportGraph (Term (Sum syntax) ann)) -- the import graph
|
||||
, [Name])) -- the list of bad names
|
||||
, EvaluatingState (Located Precise (Base term ())) term (Value (Located Precise (Base term ())))) -- the final state
|
||||
': EvaluatingEffects (Located Precise) term (Value (Located Precise))) a
|
||||
-> ( Either String -- 'fail' calls
|
||||
( Either (SomeExc (LoadError term)) -- Unhandled LoadErrors
|
||||
( ( a -- the result value
|
||||
, ImportGraph (Term (Sum syntax) ann)) -- the import graph
|
||||
, [Name])) -- the list of bad names
|
||||
, EvaluatingState (Located Precise) term (Value (Located Precise))) -- the final state
|
||||
importGraphAnalysis
|
||||
= evaluating
|
||||
. erroring @(LoadError term)
|
||||
|
Loading…
Reference in New Issue
Block a user