mirror of
https://github.com/github/semantic.git
synced 2024-12-23 23:11:50 +03:00
🔥 evaluate.
This commit is contained in:
parent
21ee656538
commit
1cc91b78dc
@ -1,7 +1,6 @@
|
|||||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, StandaloneDeriving, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, StandaloneDeriving, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||||
module Analysis.Abstract.Evaluating
|
module Analysis.Abstract.Evaluating
|
||||||
( type Evaluating
|
( type Evaluating
|
||||||
, evaluate
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Abstract.Evaluator
|
import Control.Abstract.Evaluator
|
||||||
@ -19,21 +18,6 @@ import qualified Data.IntMap as IntMap
|
|||||||
import Prelude hiding (fail)
|
import Prelude hiding (fail)
|
||||||
import Prologue
|
import Prologue
|
||||||
|
|
||||||
-- | Evaluate a term to a value.
|
|
||||||
evaluate :: forall value term effects
|
|
||||||
. ( effects ~ RequiredEffects term value (Evaluating term value effects)
|
|
||||||
, Evaluatable (Base term)
|
|
||||||
, FreeVariables term
|
|
||||||
, MonadAddressable (LocationFor value) value (Evaluating term value effects)
|
|
||||||
, MonadValue value (Evaluating term value effects)
|
|
||||||
, Recursive term
|
|
||||||
, Show (LocationFor value)
|
|
||||||
)
|
|
||||||
=> term
|
|
||||||
-> Final effects value
|
|
||||||
evaluate = runAnalysis @(Evaluating term value) . evaluateModule
|
|
||||||
|
|
||||||
|
|
||||||
-- | An analysis evaluating @term@s to @value@s with a list of @effects@ using 'Evaluatable', and producing incremental results of type @a@.
|
-- | An analysis evaluating @term@s to @value@s with a list of @effects@ using 'Evaluatable', and producing incremental results of type @a@.
|
||||||
newtype Evaluating term value effects a = Evaluating (Eff effects a)
|
newtype Evaluating term value effects a = Evaluating (Eff effects a)
|
||||||
deriving (Applicative, Functor, Effectful, Monad)
|
deriving (Applicative, Functor, Effectful, Monad)
|
||||||
|
Loading…
Reference in New Issue
Block a user