Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module exports functions, types, and typeclasses necessary for implementing a custom effect and/or effect handler.
Synopsis
- data Eff r a
- run :: Eff '[] w -> w
- eff :: (a -> b) -> (forall v. Arrs r v a -> Union r v -> b) -> Eff r a -> b
- newtype Lift m a = Lift {
- unLift :: m a
- type Lifted m r = SetMember Lift (Lift m) r
- type LiftedBase m r = (SetMember Lift (Lift m) r, MonadBaseControl m (Eff r))
- lift :: Lifted m r => m a -> Eff r a
- runLift :: Monad m => Eff '[Lift m] w -> m w
- catchDynE :: forall e a r. (Lifted IO r, Exception e) => Eff r a -> (e -> Eff r a) -> Eff r a
- data HandlerDynE r a = (Exception e, Lifted IO r) => HandlerDynE (e -> Eff r a)
- catchesDynE :: Lifted IO r => Eff r a -> [HandlerDynE r a] -> Eff r a
- data Union (r :: [* -> *]) v
- class FindElem t r => Member (t :: * -> *) r
- inj :: Member t r => t v -> Union r v
- prj :: Member t r => Union r v -> Maybe (t v)
- pattern U0' :: Member t r => t v -> Union r v
- decomp :: Union (t ': r) v -> Either (Union r v) (t v)
- pattern U0 :: t v -> Union (t ': r) v
- pattern U1 :: forall (t :: Type -> Type) (r :: [Type -> Type]) v. Union r v -> Union (t ': r) v
- class Member t r => SetMember (tag :: k -> * -> *) (t :: * -> *) r | tag r -> t
- weaken :: Union r w -> Union (any ': r) w
- class Handle t r a k where
- class Relay k r where
- handle_relay' :: r ~ (t ': r') => Relay k r' => (forall v. (Eff r a -> k) -> Arrs r v a -> t v -> k) -> (a -> k) -> (Eff r a -> k) -> Eff r a -> k
- respond_relay' :: Member t r => Relay k r => (forall v. (Eff r a -> k) -> Arrs r v a -> t v -> k) -> (a -> k) -> (Eff r a -> k) -> Eff r a -> k
- raise :: Eff r a -> Eff (e ': r) a
- send :: Member t r => t v -> Eff r v
- type Arr r a b = a -> Eff r b
- data Arrs r a b
- first :: Arr r a b -> Arr r (a, c) (b, c)
- singleK :: Arr r a b -> Arrs r a b
- qApp :: forall r b w. Arrs r b w -> Arr r b w
- (^$) :: forall r b w. Arrs r b w -> b -> Eff r w
- arr :: (a -> b) -> Arrs r a b
- ident :: Arrs r a a
- comp :: Arrs r a b -> Arrs r b c -> Arrs r a c
- (^|>) :: Arrs r a b -> Arr r b c -> Arrs r a c
- qComp :: Arrs r a b -> (Eff r b -> k) -> a -> k
- qComps :: Arrs r a b -> (Eff r b -> Eff r' c) -> Arrs r' a c
The effect monad
The monad that all effects in this library are based on.
An effectful computation is a value of type `Eff r a`.
In this signature, r
is a type-level list of effects that are being
requested and need to be handled inside an effectful computation.
a
is the computation's result similar to other monads.
A computation's result can be retrieved via the run
function.
However, all effects used in the computation need to be handled by the use
of the effects' run*
functions before unwrapping the final result.
For additional details, see the documentation of the effects you are using.
Instances
Alternative f => Handle NDet r a ([Eff r a] -> Eff r' (f w)) Source # | More performant handler; uses reified job queue |
Defined in Control.Eff.Logic.NDet handle :: (Eff r a -> [Eff r a] -> Eff r' (f w)) -> Arrs r v a -> NDet v -> [Eff r a] -> Eff r' (f w) Source # handle_relay :: (r ~ (NDet ': r'0), Relay ([Eff r a] -> Eff r' (f w)) r'0) => (a -> [Eff r a] -> Eff r' (f w)) -> (Eff r a -> [Eff r a] -> Eff r' (f w)) -> Eff r a -> [Eff r a] -> Eff r' (f w) Source # respond_relay :: (a -> [Eff r a] -> Eff r' (f w)) -> (Eff r a -> [Eff r a] -> Eff r' (f w)) -> Eff r a -> [Eff r a] -> Eff r' (f w) Source # | |
Alternative f => Handle NDet r a (Eff r' (f w)) Source # | Given a callback and |
Defined in Control.Eff.Logic.NDet handle :: (Eff r a -> Eff r' (f w)) -> Arrs r v a -> NDet v -> Eff r' (f w) Source # handle_relay :: (r ~ (NDet ': r'0), Relay (Eff r' (f w)) r'0) => (a -> Eff r' (f w)) -> (Eff r a -> Eff r' (f w)) -> Eff r a -> Eff r' (f w) Source # respond_relay :: (a -> Eff r' (f w)) -> (Eff r a -> Eff r' (f w)) -> Eff r a -> Eff r' (f w) Source # | |
(MonadBase b m, Lifted m r) => MonadBase b (Eff r) Source # | |
Defined in Control.Eff.Internal | |
MonadBase m m => MonadBaseControl m (Eff (Lift m ': ([] :: [Type -> Type]))) Source # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Writer w ': r)) Source # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Writer w ': r)) Source # | |
(MonadBase m m, LiftedBase m s) => MonadBaseControl m (Eff (Reader e ': s)) Source # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (State s ': r)) Source # | |
(MonadBase m m, LiftedBase m s) => MonadBaseControl m (Eff (Reader e ': s)) Source # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (State s ': r)) Source # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (OnDemandState s ': r)) Source # | |
Defined in Control.Eff.State.OnDemand type StM (Eff (OnDemandState s ': r)) a :: Type # liftBaseWith :: (RunInBase (Eff (OnDemandState s ': r)) m -> m a) -> Eff (OnDemandState s ': r) a # restoreM :: StM (Eff (OnDemandState s ': r)) a -> Eff (OnDemandState s ': r) a # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Fresh ': r)) Source # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff ((Exc e :: Type -> Type) ': r)) Source # | |
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (NDet ': r)) Source # | |
Monad (Eff r) Source # | |
Functor (Eff r) Source # | |
Applicative (Eff r) Source # | |
(MonadIO m, Lifted m r) => MonadIO (Eff r) Source # | |
Defined in Control.Eff.Internal | |
Member NDet r => Alternative (Eff r) Source # | |
Member NDet r => MonadPlus (Eff r) Source # | Mapping of mzero >>= f = mzero -- (L1) mzero `mplus` m = m -- (L2) m `mplus` mzero = m -- (L3) m `mplus` (n `mplus` o) = (m `mplus` n) `mplus` o -- (L4) (m `mplus` n) >>= k = (m >>= k) `mplus` (n >>= k) -- (L5)
NOTE that we do not obey the right-zero law for
m >> mzero = mzero |
Member NDet r => MSplit (Eff r) Source # | We implement LogicT, the non-determinism reflection, of which soft-cut is one instance. See the LogicT paper for an explanation. |
Relay (Eff r w) r Source # | |
Handle (Program f) r a (Intrprtr f r' -> Eff r' a) Source # | Given a continuation and a program, interpret it
Usually, we have |
Defined in Control.Eff.Operational handle :: (Eff r a -> Intrprtr f r' -> Eff r' a) -> Arrs r v a -> Program f v -> Intrprtr f r' -> Eff r' a Source # handle_relay :: (r ~ (Program f ': r'0), Relay (Intrprtr f r' -> Eff r' a) r'0) => (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source # respond_relay :: (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source # | |
Handle (Yield a b) (Yield a b ': r) w (Eff r (Y r b a)) Source # | Given a continuation and a request, respond to it |
Defined in Control.Eff.Coroutine handle :: (Eff (Yield a b ': r) w -> Eff r (Y r b a)) -> Arrs (Yield a b ': r) v w -> Yield a b v -> Eff r (Y r b a) Source # handle_relay :: ((Yield a b ': r) ~ (Yield a b ': r'), Relay (Eff r (Y r b a)) r') => (w -> Eff r (Y r b a)) -> (Eff (Yield a b ': r) w -> Eff r (Y r b a)) -> Eff (Yield a b ': r) w -> Eff r (Y r b a) Source # respond_relay :: (w -> Eff r (Y r b a)) -> (Eff (Yield a b ': r) w -> Eff r (Y r b a)) -> Eff (Yield a b ': r) w -> Eff r (Y r b a) Source # | |
type StM (Eff (Lift m ': ([] :: [Type -> Type]))) a Source # | |
type StM (Eff (Writer w ': r)) a Source # | |
type StM (Eff (Writer w ': r)) a Source # | |
type StM (Eff (Reader e ': s)) a Source # | |
type StM (Eff (State s ': r)) a Source # | |
type StM (Eff (Reader e ': s)) a Source # | |
type StM (Eff (State s ': r)) a Source # | |
type StM (Eff (OnDemandState s ': r)) a Source # | |
Defined in Control.Eff.State.OnDemand | |
type StM (Eff (Fresh ': r)) a Source # | |
type StM (Eff ((Exc e :: Type -> Type) ': r)) a Source # | |
type StM (Eff (NDet ': r)) a Source # | |
run :: Eff '[] w -> w Source #
Get the result from a pure computation
A pure computation has type Eff '[] a
. The empty effect-list indicates that
no further effects need to be handled.
Lifting operations
Lifting: emulating monad transformers
type Lifted m r = SetMember Lift (Lift m) r Source #
A convenient alias to SetMember Lift (Lift m) r
, which allows us
to assert that the lifted type occurs ony once in the effect list.
type LiftedBase m r = (SetMember Lift (Lift m) r, MonadBaseControl m (Eff r)) Source #
Same as Lifted
but with additional MonadBaseControl
constraint
lift :: Lifted m r => m a -> Eff r a Source #
embed an operation of type `m a` into the Eff
monad when Lift m
is in
a part of the effect-list.
runLift :: Monad m => Eff '[Lift m] w -> m w Source #
The handler of Lift requests. It is meant to be terminal: we only allow a single Lifted Monad. Note, too, how this is different from other handlers.
catchDynE :: forall e a r. (Lifted IO r, Exception e) => Eff r a -> (e -> Eff r a) -> Eff r a Source #
Catching of dynamic exceptions See the problem in http://okmij.org/ftp/Haskell/misc.html#catch-MonadIO
data HandlerDynE r a Source #
You need this when using catchesDynE
.
(Exception e, Lifted IO r) => HandlerDynE (e -> Eff r a) |
catchesDynE :: Lifted IO r => Eff r a -> [HandlerDynE r a] -> Eff r a Source #
Catch multiple dynamic exceptions. The implementation follows that in Control.Exception almost exactly. Not yet tested. Could this be useful for control with cut?
Open Unions
data Union (r :: [* -> *]) v Source #
The data constructors of Union are not exported
Strong Sum (Existential with the evidence) is an open union t is can be a GADT and hence not necessarily a Functor. Int is the index of t in the list r; that is, the index of t in the universe r
class FindElem t r => Member (t :: * -> *) r Source #
Typeclass that asserts that effect t
is contained inside the effect-list
r
.
The FindElem
typeclass is an implementation detail and not required for
using the effect list or implementing custom effects.
Instances
FindElem t r => Member t r Source # | |
t ~ s => Member t (s ': ([] :: [Type -> Type])) Source # | Explicit type-level equality condition is a dirty
hack to eliminate the type annotation in the trivial case,
such as There is no ambiguity when finding instances for
The only case we have to concerned about is |
pattern U0' :: Member t r => t v -> Union r v Source #
Pattern synonym to project the union onto the effect t
.
decomp :: Union (t ': r) v -> Either (Union r v) (t v) Source #
Orthogonal decomposition of the union: head and the rest.
pattern U0 :: t v -> Union (t ': r) v Source #
Some helpful pattern synonyms. U0 : the first element of the union
pattern U1 :: forall (t :: Type -> Type) (r :: [Type -> Type]) v. Union r v -> Union (t ': r) v Source #
U1 : everything excluding the first element of the union.
class Member t r => SetMember (tag :: k -> * -> *) (t :: * -> *) r | tag r -> t Source #
This class is used for emulating monad transformers
Helper functions that are used for implementing effect-handlers
class Handle t r a k where Source #
Respond to requests of type t
. The handlers themselves are expressed in
open-recursion style.
:: r ~ (t ': r') | |
=> Relay k r' | |
=> (a -> k) | return |
-> (Eff r a -> k) | untied recursive knot |
-> Eff r a | |
-> k |
A convenient pattern: given a request (in an open union), either handle it (using default Handler) or relay it.
Handle implies that all requests of type t
are dealt with, i.e., k
(the response type) doesn't have t
as part of its effect list. The Relay
k r
constraint ensures that k
is an effectful computation (with
effectlist r
).
Note that we can only handle the leftmost effect type (a consequence of the
OpenUnion
implementation.
Intercept the request and possibly respond to it, but leave it
unhandled. The Relay k r
constraint ensures that k
is an effectful
computation (with effectlist r
). As such, the effect type t
will show
up in the response type k
. There are two natural / commmon options for
k
: the implicit effect domain (i.e., Eff r (f a)), or the explicit effect
domain (i.e., s1 -> s2 -> ... -> sn -> Eff r (f a s1 s2 ... sn)).
There are three different ways in which we may want to alter behaviour:
- Before: This work should be done before
respond_relay
is called. - During: This work should be done by altering the handler being
passed to
respond_relay
. This allows us to modify the requests "in flight". - After: This work should be done be altering the
ret
being passed torespond_relay
. This allows us to overwrite changes or discard them altogether. If this seems magical, note that we have the flexibility of altering the target domaink
. Specifically, the explicit domain representation gives us access to the "effect" realm allowing us to manipulate it directly.
Instances
Handle Trace r a (IO k) Source # | Given a callback and request, respond to it |
Handle Fresh r a (Int -> k) Source # | Given a continuation and requests, respond to them |
Defined in Control.Eff.Fresh | |
Alternative f => Handle NDet r a ([Eff r a] -> Eff r' (f w)) Source # | More performant handler; uses reified job queue |
Defined in Control.Eff.Logic.NDet handle :: (Eff r a -> [Eff r a] -> Eff r' (f w)) -> Arrs r v a -> NDet v -> [Eff r a] -> Eff r' (f w) Source # handle_relay :: (r ~ (NDet ': r'0), Relay ([Eff r a] -> Eff r' (f w)) r'0) => (a -> [Eff r a] -> Eff r' (f w)) -> (Eff r a -> [Eff r a] -> Eff r' (f w)) -> Eff r a -> [Eff r a] -> Eff r' (f w) Source # respond_relay :: (a -> [Eff r a] -> Eff r' (f w)) -> (Eff r a -> [Eff r a] -> Eff r' (f w)) -> Eff r a -> [Eff r a] -> Eff r' (f w) Source # | |
Alternative f => Handle NDet r a (Eff r' (f w)) Source # | Given a callback and |
Defined in Control.Eff.Logic.NDet handle :: (Eff r a -> Eff r' (f w)) -> Arrs r v a -> NDet v -> Eff r' (f w) Source # handle_relay :: (r ~ (NDet ': r'0), Relay (Eff r' (f w)) r'0) => (a -> Eff r' (f w)) -> (Eff r a -> Eff r' (f w)) -> Eff r a -> Eff r' (f w) Source # respond_relay :: (a -> Eff r' (f w)) -> (Eff r a -> Eff r' (f w)) -> Eff r a -> Eff r' (f w) Source # | |
Monad m => Handle (Writer w) r a (b -> (w -> b -> b) -> m (a, b)) Source # | Given a value to write, and a callback (which includes empty and append), respond to requests. |
Defined in Control.Eff.Writer.Strict handle :: (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Arrs r v a -> Writer w v -> b -> (w -> b -> b) -> m (a, b) Source # handle_relay :: (r ~ (Writer w ': r'), Relay (b -> (w -> b -> b) -> m (a, b)) r') => (a -> b -> (w -> b -> b) -> m (a, b)) -> (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Eff r a -> b -> (w -> b -> b) -> m (a, b) Source # respond_relay :: (a -> b -> (w -> b -> b) -> m (a, b)) -> (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Eff r a -> b -> (w -> b -> b) -> m (a, b) Source # | |
Monad m => Handle (Writer w) r a (b -> (w -> b -> b) -> m (a, b)) Source # | Given a value to write, and a callback (which includes empty and append), respond to requests. |
Defined in Control.Eff.Writer.Lazy handle :: (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Arrs r v a -> Writer w v -> b -> (w -> b -> b) -> m (a, b) Source # handle_relay :: (r ~ (Writer w ': r'), Relay (b -> (w -> b -> b) -> m (a, b)) r') => (a -> b -> (w -> b -> b) -> m (a, b)) -> (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Eff r a -> b -> (w -> b -> b) -> m (a, b) Source # respond_relay :: (a -> b -> (w -> b -> b) -> m (a, b)) -> (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Eff r a -> b -> (w -> b -> b) -> m (a, b) Source # | |
Handle (State s) r a (s -> k) Source # | Handle 'State s' requests |
Defined in Control.Eff.State.Strict | |
Handle (State s) r a (s -> k) Source # | Handle 'State s' requests |
Defined in Control.Eff.State.Lazy | |
Handle (OnDemandState s) r a (s -> k) Source # | Given a continuation, respond to requests |
Defined in Control.Eff.State.OnDemand handle :: (Eff r a -> s -> k) -> Arrs r v a -> OnDemandState s v -> s -> k Source # handle_relay :: (r ~ (OnDemandState s ': r'), Relay (s -> k) r') => (a -> s -> k) -> (Eff r a -> s -> k) -> Eff r a -> s -> k Source # respond_relay :: (a -> s -> k) -> (Eff r a -> s -> k) -> Eff r a -> s -> k Source # | |
Monad m => Handle (Lift m) r a (m k) Source # | Handle lifted requests by running them sequentially |
Monad m => Handle (Exc e :: Type -> Type) r a (m (Either e a)) Source # | Given a callback, and an |
Defined in Control.Eff.Exception handle :: (Eff r a -> m (Either e a)) -> Arrs r v a -> Exc e v -> m (Either e a) Source # handle_relay :: (r ~ (Exc e ': r'), Relay (m (Either e a)) r') => (a -> m (Either e a)) -> (Eff r a -> m (Either e a)) -> Eff r a -> m (Either e a) Source # respond_relay :: (a -> m (Either e a)) -> (Eff r a -> m (Either e a)) -> Eff r a -> m (Either e a) Source # | |
Handle (Reader e) r a (e -> k) Source # | Given a value to read, and a callback, how to respond to requests. |
Defined in Control.Eff.Reader.Strict | |
Handle (Reader e) r a (e -> k) Source # | Given a value to read, and a callback, how to respond to requests. |
Defined in Control.Eff.Reader.Lazy | |
Handle (Program f) r a (Intrprtr f r' -> Eff r' a) Source # | Given a continuation and a program, interpret it
Usually, we have |
Defined in Control.Eff.Operational handle :: (Eff r a -> Intrprtr f r' -> Eff r' a) -> Arrs r v a -> Program f v -> Intrprtr f r' -> Eff r' a Source # handle_relay :: (r ~ (Program f ': r'0), Relay (Intrprtr f r' -> Eff r' a) r'0) => (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source # respond_relay :: (a -> Intrprtr f r' -> Eff r' a) -> (Eff r a -> Intrprtr f r' -> Eff r' a) -> Eff r a -> Intrprtr f r' -> Eff r' a Source # | |
Handle (Yield a b) (Yield a b ': r) w (Eff r (Y r b a)) Source # | Given a continuation and a request, respond to it |
Defined in Control.Eff.Coroutine handle :: (Eff (Yield a b ': r) w -> Eff r (Y r b a)) -> Arrs (Yield a b ': r) v w -> Yield a b v -> Eff r (Y r b a) Source # handle_relay :: ((Yield a b ': r) ~ (Yield a b ': r'), Relay (Eff r (Y r b a)) r') => (w -> Eff r (Y r b a)) -> (Eff (Yield a b ': r) w -> Eff r (Y r b a)) -> Eff (Yield a b ': r) w -> Eff r (Y r b a) Source # respond_relay :: (w -> Eff r (Y r b a)) -> (Eff (Yield a b ': r) w -> Eff r (Y r b a)) -> Eff (Yield a b ': r) w -> Eff r (Y r b a) Source # |
class Relay k r where Source #
Abstract the recursive relay
pattern, i.e., "somebody else's problem".
:: r ~ (t ': r') | |
=> Relay k r' | |
=> (forall v. (Eff r a -> k) -> Arrs r v a -> t v -> k) | handler |
-> (a -> k) | return |
-> (Eff r a -> k) | untied recursive knot |
-> Eff r a | |
-> k |
A less commonly needed variant with an explicit handler (instead
of Handle t r a k
constraint).
:: Member t r | |
=> Relay k r | |
=> (forall v. (Eff r a -> k) -> Arrs r v a -> t v -> k) | handler |
-> (a -> k) | return |
-> (Eff r a -> k) | recursive knot |
-> Eff r a | |
-> k |
Variant with an explicit handler (instead of Handle t r a k
constraint).
send :: Member t r => t v -> Eff r v Source #
Send a request and wait for a reply (resulting in an effectful computation).
Arrow types and compositions
type Arr r a b = a -> Eff r b Source #
Effectful arrow type: a function from a to b that also does effects denoted by r
An effectful function from a
to b
that is a composition of one or more
effectful functions. The paremeter r describes the overall effect.
The composition members are accumulated in a type-aligned queue. Using a
newtype here enables us to define Category
and Arrow
instances.