1
1
mirror of https://github.com/github/semantic.git synced 2024-12-20 21:31:48 +03:00

🔥 EvaluatingEffects.

This commit is contained in:
Rob Rix 2018-05-06 15:12:55 -04:00
parent d48349e54f
commit 32bdafe20e
2 changed files with 28 additions and 24 deletions

View File

@ -1,7 +1,6 @@
{-# LANGUAGE ScopedTypeVariables, TypeFamilies, TypeOperators #-}
module Analysis.Abstract.Evaluating
( EvaluatingState(..)
, EvaluatingEffects
, evaluating
) where
@ -23,20 +22,17 @@ deriving instance (Ord (Cell location value), Ord location, Ord term, Ord value)
deriving instance (Show (Cell location value), Show location, Show term, Show value) => Show (EvaluatingState location term value)
-- | Effects necessary for evaluating (whether concrete or abstract).
type EvaluatingEffects location term value
= '[ Fail -- Failure with an error message
, Fresh -- For allocating new addresses and/or type variables.
, Reader (Environment location value) -- Default environment used as a fallback in lookupEnv
, State (Environment location value)
, State (Heap location value)
, State (ModuleTable (Environment location value, value))
, State (Exports location value)
, State (JumpTable term)
]
evaluating :: Evaluator location term value (EvaluatingEffects location term value) result -> (Either String result, EvaluatingState location term value)
evaluating :: Evaluator location term value
'[ Fail
, Fresh
, Reader (Environment location value)
, State (Environment location value)
, State (Heap location value)
, State (ModuleTable (Environment location value, value))
, State (Exports location value)
, State (JumpTable term)
] result
-> (Either String result, EvaluatingState location term value)
evaluating
= (\ (((((result, env), heap), modules), exports), jumps) -> (result, EvaluatingState env heap modules exports jumps))
. run

View File

@ -63,15 +63,23 @@ parseModule parser rootDir file = do
importGraphAnalysis :: forall term syntax ann a
. Evaluator (Located Precise) term (Value (Located Precise))
( State (ImportGraph (Term (Sum syntax) ann))
': Resumable (AddressError (Located Precise) (Value (Located Precise)))
': Resumable ResolutionError
': Resumable (EvalError (Value (Located Precise)))
': State [Name]
': Resumable (ValueError (Located Precise) (Value (Located Precise)))
': Resumable (Unspecialized (Value (Located Precise)))
': Resumable (LoadError term)
': EvaluatingEffects (Located Precise) term (Value (Located Precise))) a
'[ State (ImportGraph (Term (Sum syntax) ann))
, Resumable (AddressError (Located Precise) (Value (Located Precise)))
, Resumable ResolutionError
, Resumable (EvalError (Value (Located Precise)))
, State [Name]
, Resumable (ValueError (Located Precise) (Value (Located Precise)))
, Resumable (Unspecialized (Value (Located Precise)))
, Resumable (LoadError term)
, Fail
, Fresh
, Reader (Environment (Located Precise) (Value (Located Precise)))
, State (Environment (Located Precise) (Value (Located Precise)))
, State (Heap (Located Precise) (Value (Located Precise)))
, State (ModuleTable (Environment (Located Precise) (Value (Located Precise)), Value (Located Precise)))
, State (Exports (Located Precise) (Value (Located Precise)))
, State (JumpTable term)
] a
-> ( Either String -- 'fail' calls
( Either (SomeExc (LoadError term)) -- Unhandled LoadErrors
( ( a -- the result value