Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
class (forall m. Functor m => Functor (e m)) => Effect e where Source #
The class for semantic effects.
An effect e
is a type e m a
, where the other types are given by:
- The
m
type variable corresponds to a monad, which will eventually be instantiated atSemantic
---meaning it is capable of encoding arbitrary other effects. - The
a
type is handled automatically and uninteresting.
The type e m
must be a Functor
, but this instance can always be given
for free via the -XDeriveFunctor
language extension. Often this instance
must be derived as a standalone (-XStandaloneDeriving
):
deriving instance Functor (MyEffect m)
If the effect doesn't use m
whatsoever it is said to be first-order.
First-order effects can be given an instance of Effect
for free with
-XDeriveAnyClass
.
deriving instance Effect MyEffect
Nothing
weave :: (Functor s, Functor m, Functor n, Typeable1 s, Typeable s) => s () -> (forall x. s (m x) -> n (s x)) -> e m a -> e n (s a) Source #
Higher-order effects require the ability to distribute state from other
effects throughout themselves. This state is given by an initial piece of
state s ()
, and a distributive law that describes how to move the state
through an effect.
When the effect e
has multiple computations in the m
monad, weave
defines the semantics for how these computations will view with the state:
- If the resulting state from one computation is fed to another, the second computation will see the state that results from the first computation.
- If instead it is given the intial state, both computations will see the same state, but the result of (at least) one will necessarily be ignored.
weave :: (Coercible (e m (s a)) (e n (s a)), Typeable1 s, Typeable s, Functor s, Functor m, Functor n) => s () -> (forall x. s (m x) -> n (s x)) -> e m a -> e n (s a) Source #
Higher-order effects require the ability to distribute state from other
effects throughout themselves. This state is given by an initial piece of
state s ()
, and a distributive law that describes how to move the state
through an effect.
When the effect e
has multiple computations in the m
monad, weave
defines the semantics for how these computations will view with the state:
- If the resulting state from one computation is fed to another, the second computation will see the state that results from the first computation.
- If instead it is given the intial state, both computations will see the same state, but the result of (at least) one will necessarily be ignored.
hoist :: (Functor m, Functor n) => (forall x. m x -> n x) -> e m a -> e n a Source #
Lift a natural transformation from m
to n
over the effect. hoist
should be defined as defaultHoist
, but can be hand-written if the
default performance isn't sufficient.
hoist :: (Coercible (e m a) (e n a), Functor m) => (forall x. m x -> n x) -> e m a -> e n a Source #
Lift a natural transformation from m
to n
over the effect. hoist
should be defined as defaultHoist
, but can be hand-written if the
default performance isn't sufficient.