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

Define an analyzeModule method on MonadAnalysis.

This allows us to chain per-module analysis in the same manner as per-term analysis.
This commit is contained in:
Rob Rix 2018-03-22 13:59:32 -04:00
parent b353b1aa5d
commit 2db0e7151b
7 changed files with 19 additions and 12 deletions

View File

@ -94,8 +94,8 @@ instance ( Corecursive term
pairs <- consultOracle c
caching c pairs (liftAnalyze analyzeTerm e)
evaluateModule m = do
c <- getConfiguration (moduleBody m)
analyzeModule m = do
c <- getConfiguration (subterm (moduleBody m))
-- Convergence here is predicated upon an Eq instance, not α-equivalence
cache <- converge (\ prevCache -> isolateCache $ do
putHeap (configurationHeap c)
@ -106,7 +106,7 @@ instance ( Corecursive term
-- that it doesn't "leak" to the calling context and diverge (otherwise this
-- would never complete). We dont need to use the values, so we 'gather' the
-- nondeterministic values into @()@.
withOracle prevCache (gather (const ()) (Caching (evaluateModule m)))) mempty
withOracle prevCache (gather (const ()) (liftAnalyze analyzeModule m))) mempty
maybe empty scatter (cacheLookup c cache)
-- | Iterate a monadic action starting from some initial seed until the results converge.

View File

@ -48,6 +48,8 @@ instance ( Effectful (m term value)
modifyHeap (gc (roots <> valueRoots v))
pure v
analyzeModule = liftAnalyze analyzeModule
-- | Retrieve the local 'Live' set.
askRoots :: (Effectful m, Member (Reader (Live (LocationFor value) value)) effects) => m effects (Live (LocationFor value) value)

View File

@ -52,6 +52,6 @@ instance ( Corecursive term
revive (embedSubterm term)
liftAnalyze analyzeTerm term
evaluateModule m = do
killAll (subterms (moduleBody m))
DeadCode (evaluateModule m)
analyzeModule m = do
killAll (subterms (subterm (moduleBody m)))
liftAnalyze analyzeModule m

View File

@ -91,7 +91,7 @@ instance ( Evaluatable (Base term)
analyzeTerm = eval
evaluateModule m = pushModule m (evaluateTerm (moduleBody m))
analyzeModule m = pushModule (subterm <$> m) (subtermValue (moduleBody m))
pushModule :: Member (Reader [Module term]) effects => Module term -> Evaluating term value effects a -> Evaluating term value effects a
pushModule m = raise . local (m :) . lower

View File

@ -40,11 +40,11 @@ instance ( Effectful (m term value)
analyzeTerm = liftAnalyze analyzeTerm
evaluateModule m = do
analyzeModule m = do
ms <- askModuleStack
let parent = maybe empty (vertex . moduleName) (listToMaybe ms)
modifyImportGraph (parent >< vertex (moduleName m) <>)
ImportGraphing (evaluateModule m)
liftAnalyze analyzeModule m
(><) :: Graph a => a -> a -> a
(><) = connect

View File

@ -38,6 +38,8 @@ instance ( Corecursive term
trace (Reducer.unit config)
liftAnalyze analyzeTerm term
analyzeModule = liftAnalyze analyzeModule
-- | Log the given trace of configurations.
trace :: ( Effectful (m term value)
, Member (Writer (trace (ConfigurationFor term value))) effects

View File

@ -3,6 +3,7 @@
module Control.Abstract.Analysis
( MonadAnalysis(..)
, evaluateTerm
, evaluateModule
, withModules
, evaluateModules
, require
@ -43,9 +44,7 @@ class (MonadEvaluator term value m, Recursive term) => MonadAnalysis term value
-- | Analyze a term using the semantics of the current analysis. This should generally only be called by definitions of 'evaluateTerm' and 'analyzeTerm' in this or other instances.
analyzeTerm :: SubtermAlgebra (Base term) term (m value)
-- | Evaluate a (root-level) term to a value using the semantics of the current analysis. This should be used to evaluate single-term programs as well as each module in multi-term programs.
evaluateModule :: Module term -> m value
evaluateModule = evaluateTerm . moduleBody
analyzeModule :: SubtermAlgebra Module term (m value)
-- | Isolate the given action with an empty global environment and exports.
isolate :: m a -> m a
@ -57,6 +56,10 @@ class (MonadEvaluator term value m, Recursive term) => MonadAnalysis term value
evaluateTerm :: MonadAnalysis term value m => term -> m value
evaluateTerm = foldSubterms analyzeTerm
-- | Evaluate a (root-level) term to a value using the semantics of the current analysis. This should be used to evaluate single-term programs as well as each module in multi-term programs.
evaluateModule :: MonadAnalysis term value m => Module term -> m value
evaluateModule m = analyzeModule (fmap (Subterm <*> evaluateTerm) m)
-- | Run an action with the a list of 'Module's available for imports.
withModules :: MonadAnalysis term value m => [Module term] -> m a -> m a