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