1
1
mirror of https://github.com/github/semantic.git synced 2024-12-30 02:14:20 +03:00

Rename handleReader to runReader.

This commit is contained in:
Rob Rix 2018-05-06 14:26:01 -04:00
parent 79e5f02108
commit 2b5e62dc33
6 changed files with 14 additions and 14 deletions

View File

@ -120,5 +120,5 @@ 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
. handleReader lowerBound
. runReader lowerBound
. raiseHandler makeChoiceA

View File

@ -54,4 +54,4 @@ reachable roots heap = go mempty roots
providingLiveSet :: Evaluator location term value (Reader (Live location value) ': effects) a -> Evaluator location term value effects a
providingLiveSet = handleReader lowerBound
providingLiveSet = runReader lowerBound

View File

@ -48,7 +48,7 @@ evaluating
. handleState lowerBound -- State (ModuleTable (Environment location value, value))
. handleState lowerBound -- State (Heap location value)
. handleState lowerBound -- State (Environment location value)
. handleReader lowerBound -- Reader (Environment location value)
. runReader lowerBound -- Reader (Environment location value)
. raiseHandler
( flip runFresh' 0
. runFail)

View File

@ -77,7 +77,7 @@ import qualified Control.Monad.Effect as Eff
import Control.Monad.Effect.Fail
import Control.Monad.Effect.Fresh
import Control.Monad.Effect.NonDet
import Control.Monad.Effect.Reader
import Control.Monad.Effect.Reader hiding (runReader)
import Control.Monad.Effect.Resumable
import Control.Monad.Effect.State
import Data.Abstract.Address

View File

@ -4,16 +4,16 @@ module Control.Effect
, throwResumable
, resume
-- * Effects
, Reader
, Eff.Reader
, State
-- * Handlers
, raiseHandler
, handleReader
, runReader
, handleState
) where
import qualified Control.Monad.Effect as Eff
import Control.Monad.Effect.Reader
import qualified Control.Monad.Effect.Reader as Eff
import Control.Monad.Effect.Resumable
import Control.Monad.Effect.State
import Prologue hiding (throwError)
@ -46,8 +46,8 @@ raiseHandler :: Effectful m => (Eff.Eff effectsA a -> Eff.Eff effectsB b) -> m e
raiseHandler handler = raise . handler . lower
-- | Run a 'Reader' effect in an 'Effectful' context.
handleReader :: Effectful m => info -> m (Reader info ': effects) a -> m effects a
handleReader = raiseHandler . flip runReader
runReader :: Effectful m => info -> m (Eff.Reader info ': effects) a -> m effects a
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)

View File

@ -333,7 +333,7 @@ evaluatePackageWith :: ( Evaluatable (Base term)
-> (SubtermAlgebra (Base term) term (Evaluator location term value termEffects value) -> SubtermAlgebra (Base term) term (Evaluator location term value termEffects value))
-> Package term
-> Evaluator location term value effects [value]
evaluatePackageWith perModule perTerm = handleReader . packageInfo <*> evaluatePackageBodyWith perModule perTerm . packageBody
evaluatePackageWith perModule perTerm = runReader . packageInfo <*> evaluatePackageBodyWith perModule perTerm . packageBody
-- | Evaluate a given package body (module table and entry points).
evaluatePackageBodyWith :: forall location term value effects termEffects moduleEffects packageBodyEffects
@ -353,8 +353,8 @@ evaluatePackageBodyWith :: forall location term value effects termEffects module
-> PackageBody term
-> Evaluator location term value effects [value]
evaluatePackageBodyWith perModule perTerm body
= handleReader (packageModules body)
. handleReader lowerBound
= runReader (packageModules body)
. runReader lowerBound
. runEvalModule
. withPrelude (packagePrelude body)
$ traverse (uncurry evaluateEntryPoint) (ModuleTable.toPairs (packageEntryPoints body))
@ -362,7 +362,7 @@ evaluatePackageBodyWith perModule perTerm body
runEvalModule = raiseHandler (relay pure (\ (EvalModule m) yield -> lower (evalModule m) >>= yield))
evalModule m
= runEvalModule
. handleReader (moduleInfo m)
. runReader (moduleInfo m)
. perModule (subtermValue . moduleBody)
. fmap (Subterm <*> evalTerm)
$ m
@ -373,7 +373,7 @@ evaluatePackageBodyWith perModule perTerm body
. runLoopControl
. foldSubterms (perTerm eval)
evaluateEntryPoint m sym = handleReader (ModuleInfo m) . runEvalClosure . runReturn . runLoopControl $ do
evaluateEntryPoint m sym = runReader (ModuleInfo m) . runEvalClosure . runReturn . runLoopControl $ do
v <- maybe unit (pure . snd) <$> require m
maybe v ((`call` []) <=< variable) sym