1
1
mirror of https://github.com/github/semantic.git synced 2024-12-29 01:42:43 +03:00

rename subtermValue to subtermRef

This commit is contained in:
Charlie Somerville 2018-05-04 13:37:20 -07:00
parent a1608bbdd9
commit 4bfc5f9ecd
3 changed files with 10 additions and 7 deletions

View File

@ -9,7 +9,7 @@ module Analysis.CallGraph
import qualified Algebra.Graph as G
import Algebra.Graph.Class
import Algebra.Graph.Export.Dot
import Data.Abstract.FreeVariables
import Data.Abstract.Evaluatable
import Data.Sum
import qualified Data.Syntax as Syntax
import qualified Data.Syntax.Declaration as Declaration
@ -47,11 +47,11 @@ class CustomCallGraphAlgebra syntax where
-- | 'Declaration.Function's produce a vertex for their name, with edges to any free variables in their body.
instance CustomCallGraphAlgebra Declaration.Function where
customCallGraphAlgebra Declaration.Function{..} bound = foldMap vertex (freeVariables (subterm functionName)) `connect` subtermValue functionBody (foldMap (freeVariables . subterm) functionParameters <> bound)
customCallGraphAlgebra Declaration.Function{..} bound = foldMap vertex (freeVariables (subterm functionName)) `connect` subtermRef functionBody (foldMap (freeVariables . subterm) functionParameters <> bound)
-- | 'Declaration.Method's produce a vertex for their name, with edges to any free variables in their body.
instance CustomCallGraphAlgebra Declaration.Method where
customCallGraphAlgebra Declaration.Method{..} bound = foldMap vertex (freeVariables (subterm methodName)) `connect` subtermValue methodBody (foldMap (freeVariables . subterm) methodParameters <> bound)
customCallGraphAlgebra Declaration.Method{..} bound = foldMap vertex (freeVariables (subterm methodName)) `connect` subtermRef methodBody (foldMap (freeVariables . subterm) methodParameters <> bound)
-- | 'Syntax.Identifier's produce a vertex iff its unbound in the 'Set'.
instance CustomCallGraphAlgebra Syntax.Identifier where
@ -72,7 +72,7 @@ class CallGraphAlgebraWithStrategy (strategy :: Strategy) syntax where
-- | The 'Default' definition of 'callGraphAlgebra' combines all of the 'CallGraph's within the @syntax@ 'Monoid'ally.
instance Foldable syntax => CallGraphAlgebraWithStrategy 'Default syntax where
callGraphAlgebraWithStrategy _ = foldMap subtermValue
callGraphAlgebraWithStrategy _ = foldMap subtermRef
-- | The 'Custom' strategy calls out to the 'customCallGraphAlgebra' method.
instance CustomCallGraphAlgebra syntax => CallGraphAlgebraWithStrategy 'Custom syntax where

View File

@ -8,6 +8,7 @@ module Data.Abstract.Evaluatable
, EvalError(..)
, runEvalError
, runEvalErrorWith
, subtermValue
, evaluateInScopedEnv
, evaluatePackageWith
, throwEvalError
@ -135,13 +136,15 @@ deriving instance Show (Unspecialized a b)
instance Show1 (Unspecialized a) where
liftShowsPrec _ _ = showsPrec
subtermValue :: Subterm t a -> a
subtermValue = subtermRef
runUnspecialized :: Evaluator location value (Resumable (Unspecialized value) ': effects) a -> Evaluator location value effects (Either (SomeExc (Unspecialized value)) a)
runUnspecialized = runResumable
runUnspecializedWith :: (forall resume . Unspecialized value resume -> Evaluator location value effects resume) -> Evaluator location value (Resumable (Unspecialized value) ': effects) a -> Evaluator location value effects a
runUnspecializedWith = runResumableWith
-- Instances
-- | If we can evaluate any syntax which can occur in a 'Sum', we can evaluate the 'Sum'.
@ -159,7 +162,7 @@ instance Evaluatable s => Evaluatable (TermF s a) where
--- 3. Only the last statements return value is returned.
instance Evaluatable [] where
-- 'nonEmpty' and 'foldMap1' enable us to return the last statements result instead of 'unit' for non-empty lists.
eval = maybe unit (runApp . foldMap1 (App . subtermValue)) . nonEmpty
eval = maybe unit (runApp . foldMap1 (App . subtermRef)) . nonEmpty
traceResolve :: (Show a, Show b, Member Trace effects) => a -> b -> Evaluator location value effects ()

View File

@ -48,7 +48,7 @@ type OpenFAlgebra f a = forall b . (b -> a) -> f b -> a
type OpenRAlgebra f t a = forall b . (b -> (t, a)) -> f b -> a
-- | A subterm and its computed value, used in 'SubtermAlgebra'.
data Subterm t a = Subterm { subterm :: !t, subtermValue :: !a }
data Subterm t a = Subterm { subterm :: !t, subtermRef :: !a }
deriving (Eq, Foldable, Functor, Generic1, Ord, Show, Traversable)
instance Bifunctor Subterm where