mirror of
https://github.com/github/semantic.git
synced 2024-12-21 22:01:46 +03:00
Merge remote-tracking branch 'origin/master' into floats-scientific
This commit is contained in:
commit
3051ffd147
@ -80,7 +80,7 @@ instance ( Corecursive t
|
|||||||
, Semigroup (Cell (LocationFor v) v)
|
, Semigroup (Cell (LocationFor v) v)
|
||||||
)
|
)
|
||||||
=> MonadAnalysis t v (CachingAnalysis t v) where
|
=> MonadAnalysis t v (CachingAnalysis t v) where
|
||||||
evaluateTerm = foldSubterms $ \e -> do
|
analyzeTerm e = do
|
||||||
c <- getConfiguration (embedSubterm e)
|
c <- getConfiguration (embedSubterm e)
|
||||||
-- Convergence here is predicated upon an Eq instance, not α-equivalence
|
-- Convergence here is predicated upon an Eq instance, not α-equivalence
|
||||||
cache <- converge (\ prevCache -> do
|
cache <- converge (\ prevCache -> do
|
||||||
|
@ -79,6 +79,6 @@ instance ( Corecursive t
|
|||||||
, Semigroup (Cell (LocationFor v) v)
|
, Semigroup (Cell (LocationFor v) v)
|
||||||
)
|
)
|
||||||
=> MonadAnalysis t v (DeadCodeAnalysis t v) where
|
=> MonadAnalysis t v (DeadCodeAnalysis t v) where
|
||||||
evaluateTerm = foldSubterms (\ term -> do
|
analyzeTerm term = do
|
||||||
revive (embedSubterm term)
|
revive (embedSubterm term)
|
||||||
eval term)
|
eval term
|
||||||
|
@ -76,4 +76,4 @@ instance ( Evaluatable (Base t)
|
|||||||
, Semigroup (Cell (LocationFor v) v)
|
, Semigroup (Cell (LocationFor v) v)
|
||||||
)
|
)
|
||||||
=> MonadAnalysis t v (Evaluation t v) where
|
=> MonadAnalysis t v (Evaluation t v) where
|
||||||
evaluateTerm = foldSubterms eval
|
analyzeTerm = eval
|
||||||
|
@ -1,9 +1,18 @@
|
|||||||
{-# LANGUAGE FunctionalDependencies #-}
|
{-# LANGUAGE DefaultSignatures, FunctionalDependencies #-}
|
||||||
module Control.Abstract.Analysis where
|
module Control.Abstract.Analysis where
|
||||||
|
|
||||||
|
import Prologue
|
||||||
|
|
||||||
-- | A 'Monad' in which one can evaluate some specific term type to some specific value type.
|
-- | A 'Monad' in which one can evaluate some specific term type to some specific value type.
|
||||||
--
|
--
|
||||||
-- This typeclass is left intentionally unconstrained to avoid circular dependencies between it and other typeclasses.
|
-- This typeclass is left intentionally unconstrained to avoid circular dependencies between it and other typeclasses.
|
||||||
class Monad m => MonadAnalysis term value m | m -> term, m -> value where
|
class Monad m => MonadAnalysis term value m | m -> term, m -> value where
|
||||||
-- | Evaluate a term to a value using the semantics of the current analysis. This should always be used instead of explicitly folding 'eval' over subterms, except in 'MonadAnalysis' instances themselves.
|
-- | 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.
|
||||||
evaluateTerm :: term -> m value
|
analyzeTerm :: SubtermAlgebra (Base term) term (m value)
|
||||||
|
|
||||||
|
-- | Evaluate a term to a value using the semantics of the current analysis.
|
||||||
|
--
|
||||||
|
-- This should always be called instead of explicitly folding either 'eval' or 'analyzeTerm' over subterms, except in 'MonadAnalysis' instances themselves.
|
||||||
|
evaluateTerm :: MonadAnalysis term value m => term -> m value
|
||||||
|
default evaluateTerm :: (MonadAnalysis term value m, Recursive term) => term -> m value
|
||||||
|
evaluateTerm = foldSubterms analyzeTerm
|
||||||
|
Loading…
Reference in New Issue
Block a user