mirror of
https://github.com/github/semantic.git
synced 2024-12-20 21:31:48 +03:00
Rename handleState to runState.
This commit is contained in:
parent
2b5e62dc33
commit
6e54b67c1f
@ -9,7 +9,7 @@ import Prologue
|
||||
|
||||
resumingBadVariables :: (AbstractHole value, Effectful m, Show value) => m (Resumable (EvalError value) ': State [Name] ': effects) a -> m effects (a, [Name])
|
||||
resumingBadVariables
|
||||
= handleState []
|
||||
= runState []
|
||||
. raiseHandler (relay pure (\ (Resumable err) yield -> traceM ("EvalError" <> show err) *> case err of
|
||||
EnvironmentLookupError{} -> yield hole
|
||||
DefaultExportError{} -> yield ()
|
||||
|
@ -119,6 +119,6 @@ scatter = foldMapA (\ (value, heap') -> putHeap heap' $> value)
|
||||
|
||||
caching :: Alternative f => Evaluator location term value (NonDet ': Reader (Cache location term value) ': State (Cache location term value) ': effects) a -> Evaluator location term value effects (f a, Cache location term value)
|
||||
caching
|
||||
= handleState lowerBound
|
||||
= runState lowerBound
|
||||
. runReader lowerBound
|
||||
. raiseHandler makeChoiceA
|
||||
|
@ -50,4 +50,4 @@ killingModules :: ( Foldable (Base term)
|
||||
killingModules recur m = killAll (subterms (subterm (moduleBody m))) *> recur m
|
||||
|
||||
providingDeadSet :: Evaluator location term value (State (Dead term) ': effects) a -> Evaluator location term value effects (a, Dead term)
|
||||
providingDeadSet = handleState lowerBound
|
||||
providingDeadSet = runState lowerBound
|
||||
|
@ -43,11 +43,11 @@ evaluating
|
||||
= (\ (((((result, env), heap), modules), exports), jumps) -> (result, EvaluatingState env heap modules exports jumps))
|
||||
. Eff.run
|
||||
. lower
|
||||
. handleState lowerBound -- State (JumpTable term)
|
||||
. handleState lowerBound -- State (Exports location value)
|
||||
. handleState lowerBound -- State (ModuleTable (Environment location value, value))
|
||||
. handleState lowerBound -- State (Heap location value)
|
||||
. handleState lowerBound -- State (Environment location value)
|
||||
. runState lowerBound -- State (JumpTable term)
|
||||
. runState lowerBound -- State (Exports location value)
|
||||
. runState lowerBound -- State (ModuleTable (Environment location value, value))
|
||||
. runState lowerBound -- State (Heap location value)
|
||||
. runState lowerBound -- State (Environment location value)
|
||||
. runReader lowerBound -- Reader (Environment location value)
|
||||
. raiseHandler
|
||||
( flip runFresh' 0
|
||||
|
@ -173,4 +173,4 @@ vertexToType Variable{} = "variable"
|
||||
|
||||
|
||||
importGraphing :: Effectful m => m (State (ImportGraph term) ': effects) result -> m effects (result, ImportGraph term)
|
||||
importGraphing = handleState mempty
|
||||
importGraphing = runState mempty
|
||||
|
@ -79,7 +79,7 @@ import Control.Monad.Effect.Fresh
|
||||
import Control.Monad.Effect.NonDet
|
||||
import Control.Monad.Effect.Reader hiding (runReader)
|
||||
import Control.Monad.Effect.Resumable
|
||||
import Control.Monad.Effect.State
|
||||
import Control.Monad.Effect.State hiding (runState)
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Configuration
|
||||
import Data.Abstract.Environment as Env
|
||||
|
@ -5,17 +5,17 @@ module Control.Effect
|
||||
, resume
|
||||
-- * Effects
|
||||
, Eff.Reader
|
||||
, State
|
||||
, Eff.State
|
||||
-- * Handlers
|
||||
, raiseHandler
|
||||
, runReader
|
||||
, handleState
|
||||
, runState
|
||||
) where
|
||||
|
||||
import qualified Control.Monad.Effect as Eff
|
||||
import qualified Control.Monad.Effect.Reader as Eff
|
||||
import Control.Monad.Effect.Resumable
|
||||
import Control.Monad.Effect.State
|
||||
import qualified Control.Monad.Effect.State as Eff
|
||||
import Prologue hiding (throwError)
|
||||
|
||||
throwResumable :: (Member (Resumable exc) effects, Effectful m) => exc v -> m effects v
|
||||
@ -50,5 +50,5 @@ runReader :: Effectful m => info -> m (Eff.Reader info ': effects) a -> m effect
|
||||
runReader = raiseHandler . flip Eff.runReader
|
||||
|
||||
-- | Run a 'State' effect in an 'Effectful' context.
|
||||
handleState :: Effectful m => state -> m (State state ': effects) a -> m effects (a, state)
|
||||
handleState = raiseHandler . flip runState
|
||||
runState :: Effectful m => state -> m (Eff.State state ': effects) a -> m effects (a, state)
|
||||
runState = raiseHandler . flip Eff.runState
|
||||
|
Loading…
Reference in New Issue
Block a user