mirror of
https://github.com/github/semantic.git
synced 2024-12-23 06:41:45 +03:00
Rename Evaluation to Evaluating.
This commit is contained in:
parent
bce888995a
commit
02347f7014
@ -16,7 +16,7 @@ type DeadCodeEffects term value = State (Dead term) ': EvaluatorEffects term val
|
||||
|
||||
-- | Run a dead code analysis of the given program.
|
||||
evaluateDead :: forall term value effects m
|
||||
. ( m ~ Evaluation term value effects
|
||||
. ( m ~ Evaluating term value effects
|
||||
, effects ~ DeadCodeEffects term value
|
||||
, Corecursive term
|
||||
, Evaluatable (Base term)
|
||||
|
@ -17,22 +17,22 @@ import System.FilePath.Posix
|
||||
evaluate :: forall value term
|
||||
. ( Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, MonadAddressable (LocationFor value) (Evaluation term value (EvaluatorEffects term value))
|
||||
, MonadValue value (Evaluation term value (EvaluatorEffects term value))
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value (EvaluatorEffects term value))
|
||||
, MonadValue value (Evaluating term value (EvaluatorEffects term value))
|
||||
, Ord (LocationFor value)
|
||||
, Recursive term
|
||||
, Semigroup (CellFor value)
|
||||
)
|
||||
=> term
|
||||
-> Final (EvaluatorEffects term value) value
|
||||
evaluate = run @(EvaluatorEffects term value) . runEvaluator . runEvaluation . evaluateTerm
|
||||
evaluate = run @(EvaluatorEffects term value) . runEvaluator . runEvaluating . evaluateTerm
|
||||
|
||||
-- | Evaluate terms and an entry point to a value.
|
||||
evaluates :: forall value term
|
||||
. ( Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, MonadAddressable (LocationFor value) (Evaluation term value (EvaluatorEffects term value))
|
||||
, MonadValue value (Evaluation term value (EvaluatorEffects term value))
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value (EvaluatorEffects term value))
|
||||
, MonadValue value (Evaluating term value (EvaluatorEffects term value))
|
||||
, Ord (LocationFor value)
|
||||
, Recursive term
|
||||
, Semigroup (CellFor value)
|
||||
@ -40,7 +40,7 @@ evaluates :: forall value term
|
||||
=> [(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 (runEvaluation (withModules pairs (evaluateTerm t))))
|
||||
evaluates pairs (_, t) = run @(EvaluatorEffects term value) (runEvaluator (runEvaluating (withModules pairs (evaluateTerm 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
|
||||
@ -48,22 +48,22 @@ withModules pairs = localModuleTable (const moduleTable)
|
||||
where moduleTable = Linker (Map.fromList (map (first (dropExtensions . blobPath)) pairs))
|
||||
|
||||
-- | An analysis performing concrete evaluation of @term@s to @value@s.
|
||||
newtype Evaluation term value effects a = Evaluation { runEvaluation :: Evaluator term value effects a }
|
||||
newtype Evaluating term value effects a = Evaluating { runEvaluating :: Evaluator term value effects a }
|
||||
deriving (Applicative, Functor, LiftEffect, Monad)
|
||||
|
||||
deriving instance Member Fail effects => MonadFail (Evaluation term value effects)
|
||||
deriving instance Member Fresh effects => MonadFresh (Evaluation term value effects)
|
||||
deriving instance Member NonDetEff effects => Alternative (Evaluation term value effects)
|
||||
deriving instance Member NonDetEff effects => MonadNonDet (Evaluation term value effects)
|
||||
deriving instance (Member Fail effects, MonadEvaluator (Evaluator term value effects), Ord (LocationFor value)) => MonadEvaluator (Evaluation term value effects)
|
||||
deriving instance Member Fail effects => MonadFail (Evaluating term value effects)
|
||||
deriving instance Member Fresh effects => MonadFresh (Evaluating term value effects)
|
||||
deriving instance Member NonDetEff effects => Alternative (Evaluating term value effects)
|
||||
deriving instance Member NonDetEff effects => MonadNonDet (Evaluating term value effects)
|
||||
deriving instance (Member Fail effects, MonadEvaluator (Evaluator term value effects), Ord (LocationFor value)) => MonadEvaluator (Evaluating term value effects)
|
||||
|
||||
instance ( Evaluatable (Base term)
|
||||
, FreeVariables term
|
||||
, Members (EvaluatorEffects term value) effects
|
||||
, MonadAddressable (LocationFor value) (Evaluation term value effects)
|
||||
, MonadValue value (Evaluation term value effects)
|
||||
, MonadAddressable (LocationFor value) (Evaluating term value effects)
|
||||
, MonadValue value (Evaluating term value effects)
|
||||
, Recursive term
|
||||
, Semigroup (CellFor value)
|
||||
)
|
||||
=> MonadAnalysis (Evaluation term value effects) where
|
||||
=> MonadAnalysis (Evaluating term value effects) where
|
||||
analyzeTerm = eval
|
||||
|
@ -45,9 +45,9 @@ evaluateRubyFiles paths = do
|
||||
pure $ evaluates @RubyValue (zip bs ts) (b, t)
|
||||
|
||||
-- Python
|
||||
typecheckPythonFile path = run . lower @(CachingAnalysis (Evaluation 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 (EvaluatorEffects Python.Term Type)))) . evaluateTerm <$> (file path >>= runTask . parse pythonParser)
|
||||
|
||||
tracePythonFile path = run . lower @(TracingAnalysis [] (Evaluation Python.Term PythonValue (TracingEffects [] Python.Term PythonValue))) . 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)
|
||||
|
||||
evaluatePythonFile path = evaluate @PythonValue <$>
|
||||
(file path >>= runTask . parse pythonParser)
|
||||
|
Loading…
Reference in New Issue
Block a user