Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides an InterpretC
carrier capable of interpreting an arbitrary effect using a passed-in higher order function to interpret that effect. This is suitable for prototyping new effects quickly.
Synopsis
- runInterpret :: (HFunctor eff, Monad m) => (forall x. eff m x -> m x) -> (forall s. Reifies s (Handler eff m) => InterpretC s eff m a) -> m a
- runInterpretState :: (HFunctor eff, Monad m) => (forall x. s -> eff (StateC s m) x -> m (s, x)) -> s -> (forall t. Reifies t (Handler eff (StateC s m)) => InterpretC t eff (StateC s m) a) -> m (s, a)
- newtype InterpretC s (sig :: (* -> *) -> * -> *) m a = InterpretC (m a)
- class Reifies s a | s -> a
- data Handler sig m
- class (HFunctor sig, Monad m) => Algebra sig m | m -> sig
- type Has eff sig m = (Members eff sig, Algebra sig m)
- run :: Identity a -> a
Interpret carrier
runInterpret :: (HFunctor eff, Monad m) => (forall x. eff m x -> m x) -> (forall s. Reifies s (Handler eff m) => InterpretC s eff m a) -> m a Source #
Interpret an effect using a higher-order function.
Note that due to the higher-rank type, you have to use either $
or explicit application when applying this interpreter. That is, you will need to write runInterpret f (runInterpret g myPrgram)
or runInterpret f $ runInterpret g $ myProgram
. If you try and write runInterpret f . runInterpret g
, you will unfortunately get a rather scary type error!
Since: 1.0.0.0
runInterpretState :: (HFunctor eff, Monad m) => (forall x. s -> eff (StateC s m) x -> m (s, x)) -> s -> (forall t. Reifies t (Handler eff (StateC s m)) => InterpretC t eff (StateC s m) a) -> m (s, a) Source #
Interpret an effect using a higher-order function with some state variable.
Since: 1.0.0.0
newtype InterpretC s (sig :: (* -> *) -> * -> *) m a Source #
Since: 1.0.0.0
InterpretC (m a) |
Instances
A Handler
is a function that interprets effects described by sig
into the carrier monad m
.
Re-exports
class (HFunctor sig, Monad m) => Algebra sig m | m -> sig Source #
The class of carriers (results) for algebras (effect handlers) over signatures (effects), whose actions are given by the alg
method.
Since: 1.0.0.0
Instances
type Has eff sig m = (Members eff sig, Algebra sig m) Source #
m
is a carrier for sig
containing eff
.
Note that if eff
is a sum, it will be decomposed into multiple Member
constraints. While this technically allows one to combine multiple unrelated effects into a single Has
constraint, doing so has two significant drawbacks:
- Due to a problem with recursive type families, this can lead to significantly slower compiles.
- It defeats
ghc
’s warnings for redundant constraints, and thus can lead to a proliferation of redundant constraints as code is changed.