extensible-effects-5.0.0.1: An Alternative to Monad Transformers

Safe HaskellSafe
LanguageHaskell2010

Control.Eff.Extend

Contents

Description

This module exports functions, types, and typeclasses necessary for implementing a custom effect and/or effect handler.

Synopsis

The effect monad

data Eff r a Source #

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.

Constructors

Val a 
E (Arrs r b a) (Union r b) 
Instances
Alternative f => Handle NDet r a ([Eff r a] -> Eff r' (f w)) Source #

More performant handler; uses reified job queue

Instance details

Defined in Control.Eff.Logic.NDet

Methods

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 NDet requests respond to them. Note that this makes explicit that we rely on f to have enough room to store all possibilities.

Instance details

Defined in Control.Eff.Logic.NDet

Methods

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 # 
Instance details

Defined in Control.Eff.Internal

Methods

liftBase :: b α -> Eff r α #

MonadBase m m => MonadBaseControl m (Eff (Lift m ': ([] :: [Type -> Type]))) Source # 
Instance details

Defined in Control.Eff.Internal

Associated Types

type StM (Eff (Lift m ': [])) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Lift m ': [])) m -> m a) -> Eff (Lift m ': []) a #

restoreM :: StM (Eff (Lift m ': [])) a -> Eff (Lift m ': []) a #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Writer w ': r)) Source # 
Instance details

Defined in Control.Eff.Writer.Strict

Associated Types

type StM (Eff (Writer w ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Writer w ': r)) m -> m a) -> Eff (Writer w ': r) a #

restoreM :: StM (Eff (Writer w ': r)) a -> Eff (Writer w ': r) a #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Writer w ': r)) Source # 
Instance details

Defined in Control.Eff.Writer.Lazy

Associated Types

type StM (Eff (Writer w ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Writer w ': r)) m -> m a) -> Eff (Writer w ': r) a #

restoreM :: StM (Eff (Writer w ': r)) a -> Eff (Writer w ': r) a #

(MonadBase m m, LiftedBase m s) => MonadBaseControl m (Eff (Reader e ': s)) Source # 
Instance details

Defined in Control.Eff.Reader.Strict

Associated Types

type StM (Eff (Reader e ': s)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Reader e ': s)) m -> m a) -> Eff (Reader e ': s) a #

restoreM :: StM (Eff (Reader e ': s)) a -> Eff (Reader e ': s) a #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (State s ': r)) Source # 
Instance details

Defined in Control.Eff.State.Strict

Associated Types

type StM (Eff (State s ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (State s ': r)) m -> m a) -> Eff (State s ': r) a #

restoreM :: StM (Eff (State s ': r)) a -> Eff (State s ': r) a #

(MonadBase m m, LiftedBase m s) => MonadBaseControl m (Eff (Reader e ': s)) Source # 
Instance details

Defined in Control.Eff.Reader.Lazy

Associated Types

type StM (Eff (Reader e ': s)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Reader e ': s)) m -> m a) -> Eff (Reader e ': s) a #

restoreM :: StM (Eff (Reader e ': s)) a -> Eff (Reader e ': s) a #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (State s ': r)) Source # 
Instance details

Defined in Control.Eff.State.Lazy

Associated Types

type StM (Eff (State s ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (State s ': r)) m -> m a) -> Eff (State s ': r) a #

restoreM :: StM (Eff (State s ': r)) a -> Eff (State s ': r) a #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (OnDemandState s ': r)) Source # 
Instance details

Defined in Control.Eff.State.OnDemand

Associated Types

type StM (Eff (OnDemandState s ': r)) a :: Type #

Methods

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 # 
Instance details

Defined in Control.Eff.Fresh

Associated Types

type StM (Eff (Fresh ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Fresh ': r)) m -> m a) -> Eff (Fresh ': r) a #

restoreM :: StM (Eff (Fresh ': r)) a -> Eff (Fresh ': r) a #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff ((Exc e :: Type -> Type) ': r)) Source # 
Instance details

Defined in Control.Eff.Exception

Associated Types

type StM (Eff (Exc e ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Exc e ': r)) m -> m a) -> Eff (Exc e ': r) a #

restoreM :: StM (Eff (Exc e ': r)) a -> Eff (Exc e ': r) a #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (NDet ': r)) Source # 
Instance details

Defined in Control.Eff.Logic.NDet

Associated Types

type StM (Eff (NDet ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (NDet ': r)) m -> m a) -> Eff (NDet ': r) a #

restoreM :: StM (Eff (NDet ': r)) a -> Eff (NDet ': r) a #

Monad (Eff r) Source # 
Instance details

Defined in Control.Eff.Internal

Methods

(>>=) :: Eff r a -> (a -> Eff r b) -> Eff r b #

(>>) :: Eff r a -> Eff r b -> Eff r b #

return :: a -> Eff r a #

fail :: String -> Eff r a #

Functor (Eff r) Source # 
Instance details

Defined in Control.Eff.Internal

Methods

fmap :: (a -> b) -> Eff r a -> Eff r b #

(<$) :: a -> Eff r b -> Eff r a #

Applicative (Eff r) Source # 
Instance details

Defined in Control.Eff.Internal

Methods

pure :: a -> Eff r a #

(<*>) :: Eff r (a -> b) -> Eff r a -> Eff r b #

liftA2 :: (a -> b -> c) -> Eff r a -> Eff r b -> Eff r c #

(*>) :: Eff r a -> Eff r b -> Eff r b #

(<*) :: Eff r a -> Eff r b -> Eff r a #

(MonadIO m, Lifted m r) => MonadIO (Eff r) Source # 
Instance details

Defined in Control.Eff.Internal

Methods

liftIO :: IO a -> Eff r a #

Member NDet r => Alternative (Eff r) Source # 
Instance details

Defined in Control.Eff.Logic.NDet

Methods

empty :: Eff r a #

(<|>) :: Eff r a -> Eff r a -> Eff r a #

some :: Eff r a -> Eff r [a] #

many :: Eff r a -> Eff r [a] #

Member NDet r => MonadPlus (Eff r) Source #

Mapping of NDet requests to MonadPlus. We obey the following laws (taken from the Backtr and @LogicT papers):

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)
  • L1 is the left-zero law for mzero
  • L2, L3, L4 are the Monoid laws

NOTE that we do not obey the right-zero law for mzero. Specifically, we do not obey:

m >> mzero  = mzero
Instance details

Defined in Control.Eff.Logic.NDet

Methods

mzero :: Eff r a #

mplus :: Eff r a -> Eff r a -> Eff r a #

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.

Instance details

Defined in Control.Eff.Logic.NDet

Methods

msplit :: Eff r a -> Eff r (Maybe (a, Eff r a)) Source #

Relay (Eff r w) r Source # 
Instance details

Defined in Control.Eff.Internal

Methods

relay :: (v -> Eff r w) -> Union r v -> Eff r w Source #

Handle (Program f) r a (Intrprtr f r' -> Eff r' a) Source #

Given a continuation and a program, interpret it Usually, we have r ~ [Program f : r']

Instance details

Defined in Control.Eff.Operational

Methods

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

Instance details

Defined in Control.Eff.Coroutine

Methods

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 # 
Instance details

Defined in Control.Eff.Internal

type StM (Eff (Lift m ': ([] :: [Type -> Type]))) a = a
type StM (Eff (Writer w ': r)) a Source # 
Instance details

Defined in Control.Eff.Writer.Strict

type StM (Eff (Writer w ': r)) a = StM (Eff r) (a, [w])
type StM (Eff (Writer w ': r)) a Source # 
Instance details

Defined in Control.Eff.Writer.Lazy

type StM (Eff (Writer w ': r)) a = StM (Eff r) (a, [w])
type StM (Eff (Reader e ': s)) a Source # 
Instance details

Defined in Control.Eff.Reader.Strict

type StM (Eff (Reader e ': s)) a = StM (Eff s) a
type StM (Eff (State s ': r)) a Source # 
Instance details

Defined in Control.Eff.State.Strict

type StM (Eff (State s ': r)) a = StM (Eff r) (a, s)
type StM (Eff (Reader e ': s)) a Source # 
Instance details

Defined in Control.Eff.Reader.Lazy

type StM (Eff (Reader e ': s)) a = StM (Eff s) a
type StM (Eff (State s ': r)) a Source # 
Instance details

Defined in Control.Eff.State.Lazy

type StM (Eff (State s ': r)) a = StM (Eff r) (a, s)
type StM (Eff (OnDemandState s ': r)) a Source # 
Instance details

Defined in Control.Eff.State.OnDemand

type StM (Eff (OnDemandState s ': r)) a = StM (Eff r) (a, s)
type StM (Eff (Fresh ': r)) a Source # 
Instance details

Defined in Control.Eff.Fresh

type StM (Eff (Fresh ': r)) a = StM (Eff r) (a, Int)
type StM (Eff ((Exc e :: Type -> Type) ': r)) a Source # 
Instance details

Defined in Control.Eff.Exception

type StM (Eff ((Exc e :: Type -> Type) ': r)) a = StM (Eff r) (Either e a)
type StM (Eff (NDet ': r)) a Source # 
Instance details

Defined in Control.Eff.Logic.NDet

type StM (Eff (NDet ': r)) a = StM (Eff r) [a]

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.

eff :: (a -> b) -> (forall v. Arrs r v a -> Union r v -> b) -> Eff r a -> b Source #

Case analysis for Eff datatype. If the value is Val a apply the first function to a; if it is E u q, apply the second function.

Lifting operations

newtype Lift m a Source #

Lifting: emulating monad transformers

Constructors

Lift 

Fields

Instances
MonadBase m m => MonadBaseControl m (Eff (Lift m ': ([] :: [Type -> Type]))) Source # 
Instance details

Defined in Control.Eff.Internal

Associated Types

type StM (Eff (Lift m ': [])) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Lift m ': [])) m -> m a) -> Eff (Lift m ': []) a #

restoreM :: StM (Eff (Lift m ': [])) a -> Eff (Lift m ': []) a #

Monad m => Handle (Lift m) r a (m k) Source #

Handle lifted requests by running them sequentially

Instance details

Defined in Control.Eff.Internal

Methods

handle :: (Eff r a -> m k) -> Arrs r v a -> Lift m v -> m k Source #

handle_relay :: (r ~ (Lift m ': r'), Relay (m k) r') => (a -> m k) -> (Eff r a -> m k) -> Eff r a -> m k Source #

respond_relay :: (a -> m k) -> (Eff r a -> m k) -> Eff r a -> m k Source #

type StM (Eff (Lift m ': ([] :: [Type -> Type]))) a Source # 
Instance details

Defined in Control.Eff.Internal

type StM (Eff (Lift m ': ([] :: [Type -> Type]))) a = a

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.

Constructors

(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.

Minimal complete definition

inj, prj

Instances
FindElem t r => Member t r Source # 
Instance details

Defined in Data.OpenUnion

Methods

inj :: t v -> Union r v Source #

prj :: Union r v -> Maybe (t v) 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 run (runReader () get).

There is no ambiguity when finding instances for Member t (a ': b ': r), which the second instance is selected.

The only case we have to concerned about is Member t '[s]. But, in this case, values of definition is the same (if present), and the first one is chosen according to GHC User Manual, since the latter one is incoherent. This is the optimal choice.

Instance details

Defined in Data.OpenUnion

Methods

inj :: t v -> Union (s ': []) v Source #

prj :: Union (s ': []) v -> Maybe (t v) Source #

inj :: Member t r => t v -> Union r v Source #

prj :: Member t r => Union r v -> Maybe (t v) Source #

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

Instances
(EQU t1 t2 p, MemberU' p tag t1 (t2 ': r)) => SetMember (tag :: k -> Type -> Type) t1 (t2 ': r) Source # 
Instance details

Defined in Data.OpenUnion

weaken :: Union r w -> Union (any ': r) w Source #

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.

Minimal complete definition

handle

Methods

handle Source #

Arguments

:: (Eff r a -> k)

untied recursive knot

-> Arrs r v a

coroutine awaiting response

-> t v

request

-> k 

handle_relay Source #

Arguments

:: 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.

respond_relay Source #

Arguments

:: Member t r 
=> Relay k r 
=> (a -> k)

return

-> (Eff r a -> k)

untied recursive knot

-> Eff r a 
-> k 

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:

  1. Before: This work should be done before respond_relay is called.
  2. During: This work should be done by altering the handler being passed to respond_relay. This allows us to modify the requests "in flight".
  3. After: This work should be done be altering the ret being passed to respond_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 domain k. 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

Instance details

Defined in Control.Eff.Trace

Methods

handle :: (Eff r a -> IO k) -> Arrs r v a -> Trace v -> IO k Source #

handle_relay :: (r ~ (Trace ': r'), Relay (IO k) r') => (a -> IO k) -> (Eff r a -> IO k) -> Eff r a -> IO k Source #

respond_relay :: (a -> IO k) -> (Eff r a -> IO k) -> Eff r a -> IO k Source #

Handle Fresh r a (Int -> k) Source #

Given a continuation and requests, respond to them

Instance details

Defined in Control.Eff.Fresh

Methods

handle :: (Eff r a -> Int -> k) -> Arrs r v a -> Fresh v -> Int -> k Source #

handle_relay :: (r ~ (Fresh ': r'), Relay (Int -> k) r') => (a -> Int -> k) -> (Eff r a -> Int -> k) -> Eff r a -> Int -> k Source #

respond_relay :: (a -> Int -> k) -> (Eff r a -> Int -> k) -> Eff r a -> Int -> k Source #

Alternative f => Handle NDet r a ([Eff r a] -> Eff r' (f w)) Source #

More performant handler; uses reified job queue

Instance details

Defined in Control.Eff.Logic.NDet

Methods

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 NDet requests respond to them. Note that this makes explicit that we rely on f to have enough room to store all possibilities.

Instance details

Defined in Control.Eff.Logic.NDet

Methods

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.

Instance details

Defined in Control.Eff.Writer.Strict

Methods

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.

Instance details

Defined in Control.Eff.Writer.Lazy

Methods

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

Instance details

Defined in Control.Eff.State.Strict

Methods

handle :: (Eff r a -> s -> k) -> Arrs r v a -> State s v -> s -> k Source #

handle_relay :: (r ~ (State 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 #

Handle (State s) r a (s -> k) Source #

Handle 'State s' requests

Instance details

Defined in Control.Eff.State.Lazy

Methods

handle :: (Eff r a -> s -> k) -> Arrs r v a -> State s v -> s -> k Source #

handle_relay :: (r ~ (State 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 #

Handle (OnDemandState s) r a (s -> k) Source #

Given a continuation, respond to requests

Instance details

Defined in Control.Eff.State.OnDemand

Methods

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

Instance details

Defined in Control.Eff.Internal

Methods

handle :: (Eff r a -> m k) -> Arrs r v a -> Lift m v -> m k Source #

handle_relay :: (r ~ (Lift m ': r'), Relay (m k) r') => (a -> m k) -> (Eff r a -> m k) -> Eff r a -> m k Source #

respond_relay :: (a -> m k) -> (Eff r a -> m k) -> Eff r a -> m k Source #

Monad m => Handle (Exc e :: Type -> Type) r a (m (Either e a)) Source #

Given a callback, and an Exc request, respond to it.

Instance details

Defined in Control.Eff.Exception

Methods

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.

Instance details

Defined in Control.Eff.Reader.Strict

Methods

handle :: (Eff r a -> e -> k) -> Arrs r v a -> Reader e v -> e -> k Source #

handle_relay :: (r ~ (Reader e ': r'), Relay (e -> k) r') => (a -> e -> k) -> (Eff r a -> e -> k) -> Eff r a -> e -> k Source #

respond_relay :: (a -> e -> k) -> (Eff r a -> e -> k) -> Eff r a -> e -> k Source #

Handle (Reader e) r a (e -> k) Source #

Given a value to read, and a callback, how to respond to requests.

Instance details

Defined in Control.Eff.Reader.Lazy

Methods

handle :: (Eff r a -> e -> k) -> Arrs r v a -> Reader e v -> e -> k Source #

handle_relay :: (r ~ (Reader e ': r'), Relay (e -> k) r') => (a -> e -> k) -> (Eff r a -> e -> k) -> Eff r a -> e -> k Source #

respond_relay :: (a -> e -> k) -> (Eff r a -> e -> k) -> Eff r a -> e -> k Source #

Handle (Program f) r a (Intrprtr f r' -> Eff r' a) Source #

Given a continuation and a program, interpret it Usually, we have r ~ [Program f : r']

Instance details

Defined in Control.Eff.Operational

Methods

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

Instance details

Defined in Control.Eff.Coroutine

Methods

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".

Methods

relay :: (v -> k) -> Union r v -> k Source #

Instances
Relay k r => Relay (s -> k) r Source # 
Instance details

Defined in Control.Eff.Internal

Methods

relay :: (v -> s -> k) -> Union r v -> s -> k Source #

Relay (Eff r w) r Source # 
Instance details

Defined in Control.Eff.Internal

Methods

relay :: (v -> Eff r w) -> Union r v -> Eff r w Source #

handle_relay' Source #

Arguments

:: 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).

respond_relay' Source #

Arguments

:: 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).

raise :: Eff r a -> Eff (e ': r) a Source #

Embeds a less-constrained Eff into a more-constrained one. Analogous to MTL's lift.

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

data Arrs r a b Source #

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.

Instances
Arrow (Arrs r) Source #

As the name suggests, Arrs also has an Arrow instance.

Instance details

Defined in Control.Eff.Internal

Methods

arr :: (b -> c) -> Arrs r b c #

first :: Arrs r b c -> Arrs r (b, d) (c, d) #

second :: Arrs r b c -> Arrs r (d, b) (d, c) #

(***) :: Arrs r b c -> Arrs r b' c' -> Arrs r (b, b') (c, c') #

(&&&) :: Arrs r b c -> Arrs r b c' -> Arrs r b (c, c') #

Category (Arrs r :: Type -> Type -> Type) Source #

Arrs can be composed and have a natural identity.

Instance details

Defined in Control.Eff.Internal

Methods

id :: Arrs r a a #

(.) :: Arrs r b c -> Arrs r a b -> Arrs r a c #

first :: Arr r a b -> Arr r (a, c) (b, c) Source #

singleK :: Arr r a b -> Arrs r a b Source #

convert single effectful arrow into composable type. i.e., convert Arr to Arrs

qApp :: forall r b w. Arrs r b w -> Arr r b w Source #

Application to the `generalized effectful function' Arrs r b w, i.e., convert Arrs to Arr

(^$) :: forall r b w. Arrs r b w -> b -> Eff r w Source #

Syntactic sugar for qApp

arr :: (a -> b) -> Arrs r a b Source #

Lift a function to an arrow

ident :: Arrs r a a Source #

The identity arrow

comp :: Arrs r a b -> Arrs r b c -> Arrs r a c Source #

Arrow composition

(^|>) :: Arrs r a b -> Arr r b c -> Arrs r a c Source #

Common pattern: append Arr to Arrs

qComp :: Arrs r a b -> (Eff r b -> k) -> a -> k Source #

Compose effectful arrows (and possibly change the effect!)

qComps :: Arrs r a b -> (Eff r b -> Eff r' c) -> Arrs r' a c Source #

Compose effectful arrows (and possibly change the effect!)