mirror of
https://github.com/github/semantic.git
synced 2024-12-23 06:41:45 +03:00
Rename EvaluatorEffects to EvaluatingEffects.
This commit is contained in:
parent
fa93a23368
commit
3f358a4cce
@ -9,7 +9,7 @@ import Data.Set (delete)
|
||||
import Prologue
|
||||
|
||||
-- | The effects necessary for dead code analysis.
|
||||
type DeadCodeEffects term value = State (Dead term) ': EvaluatorEffects term value
|
||||
type DeadCodeEffects term value = State (Dead term) ': EvaluatingEffects term value
|
||||
|
||||
|
||||
-- | Run a dead code analysis of the given program.
|
||||
|
@ -17,30 +17,30 @@ import System.FilePath.Posix
|
||||
evaluate :: forall value term
|
||||
. ( Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value (EvaluatorEffects term value))
|
||||
, MonadValue value (Evaluating term value (EvaluatorEffects term value))
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value (EvaluatingEffects term value))
|
||||
, MonadValue value (Evaluating term value (EvaluatingEffects term value))
|
||||
, Ord (LocationFor value)
|
||||
, Recursive term
|
||||
, Semigroup (CellFor value)
|
||||
)
|
||||
=> term
|
||||
-> Final (EvaluatorEffects term value) value
|
||||
evaluate = run @(EvaluatorEffects term value) . runEvaluator . runEvaluating . evaluateModule
|
||||
-> Final (EvaluatingEffects term value) value
|
||||
evaluate = run @(EvaluatingEffects term value) . runEvaluator . runEvaluating . evaluateModule
|
||||
|
||||
-- | Evaluate terms and an entry point to a value.
|
||||
evaluates :: forall value term
|
||||
. ( Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value (EvaluatorEffects term value))
|
||||
, MonadValue value (Evaluating term value (EvaluatorEffects term value))
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value (EvaluatingEffects term value))
|
||||
, MonadValue value (Evaluating term value (EvaluatingEffects term value))
|
||||
, Ord (LocationFor value)
|
||||
, Recursive term
|
||||
, Semigroup (CellFor value)
|
||||
)
|
||||
=> [(Blob, term)] -- List of (blob, term) pairs that make up the program to be evaluated
|
||||
-> (Blob, term) -- Entrypoint
|
||||
-> Final (EvaluatorEffects term value) value
|
||||
evaluates pairs (_, t) = run @(EvaluatorEffects term value) (runEvaluator (runEvaluating (withModules pairs (evaluateModule t))))
|
||||
-> Final (EvaluatingEffects term value) value
|
||||
evaluates pairs (_, t) = run @(EvaluatingEffects term value) (runEvaluator (runEvaluating (withModules pairs (evaluateModule t))))
|
||||
|
||||
-- | Run an action with the passed ('Blob', @term@) pairs available for imports.
|
||||
withModules :: (MonadAnalysis m, MonadEvaluator m) => [(Blob, TermFor m)] -> m a -> m a
|
||||
@ -59,7 +59,7 @@ deriving instance (Member Fail effects, MonadEvaluator (Evaluator term value eff
|
||||
|
||||
instance ( Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, Members (EvaluatorEffects term value) effects
|
||||
, Members (EvaluatingEffects term value) effects
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value effects)
|
||||
, MonadValue value (Evaluating term value effects)
|
||||
, Recursive term
|
||||
|
@ -14,7 +14,7 @@ type Tracer trace term value = Writer (Trace trace term value)
|
||||
type TracerFor trace m = Writer (TraceFor trace m)
|
||||
|
||||
-- | The effects necessary for tracing analyses.
|
||||
type TracingEffects trace term value = Tracer trace term value ': EvaluatorEffects term value
|
||||
type TracingEffects trace term value = Tracer trace term value ': EvaluatingEffects term value
|
||||
|
||||
-- | Trace analysis.
|
||||
--
|
||||
|
@ -58,7 +58,7 @@ class MonadFail m => MonadEvaluator m where
|
||||
getConfiguration :: Ord (LocationFor (ValueFor m)) => term -> m (Configuration (LocationFor (ValueFor m)) term (ValueFor m))
|
||||
getConfiguration term = Configuration term <$> askRoots <*> askLocalEnv <*> getStore
|
||||
|
||||
type EvaluatorEffects term value
|
||||
type EvaluatingEffects term value
|
||||
= '[ Fail -- Failure with an error message
|
||||
, Reader (EnvironmentFor value) -- Local environment (e.g. binding over a closure)
|
||||
, State (EnvironmentFor value) -- Global (imperative) environment
|
||||
@ -67,7 +67,7 @@ type EvaluatorEffects term value
|
||||
, State (Linker value) -- Cache of evaluated modules
|
||||
]
|
||||
|
||||
instance (Ord (LocationFor value), Members (EvaluatorEffects term value) effects) => MonadEvaluator (Evaluator term value effects) where
|
||||
instance (Ord (LocationFor value), Members (EvaluatingEffects term value) effects) => MonadEvaluator (Evaluator term value effects) where
|
||||
type TermFor (Evaluator term value effects) = term
|
||||
type ValueFor (Evaluator term value effects) = value
|
||||
|
||||
|
@ -46,7 +46,7 @@ evaluateRubyFiles paths = do
|
||||
pure $ evaluates @RubyValue (zip bs ts) (b, t)
|
||||
|
||||
-- Python
|
||||
typecheckPythonFile path = run . lower @(CachingAnalysis (Evaluating Python.Term Type (CachingEffects Python.Term Type (EvaluatorEffects Python.Term Type)))) . evaluateTerm <$> (file path >>= runTask . parse pythonParser)
|
||||
typecheckPythonFile path = run . lower @(CachingAnalysis (Evaluating Python.Term Type (CachingEffects Python.Term Type (EvaluatingEffects Python.Term Type)))) . evaluateTerm <$> (file path >>= runTask . parse pythonParser)
|
||||
|
||||
tracePythonFile path = run . lower @(TracingAnalysis [] (Evaluating Python.Term PythonValue (TracingEffects [] Python.Term PythonValue))) . evaluateTerm <$> (file path >>= runTask . parse pythonParser)
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user