Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
A monadic library for communication between a handler and its client, the administered computation
Original work available at http://okmij.org/ftp/Haskell/extensible/tutorial.html. This module implements extensible effects as an alternative to monad transformers, as described in http://okmij.org/ftp/Haskell/extensible/exteff.pdf and http://okmij.org/ftp/Haskell/extensible/more.pdf.
Extensible Effects are implemented as typeclass constraints on an Eff[ect] datatype. A contrived example can be found under Control.Eff.Example. To run the effects, consult the tests.
- type Arr r a b = a -> Eff r b
- type Arrs r a b = FTCQueue (Eff r) a b
- single :: Arr r a b -> Arrs r a b
- first :: Arr r a b -> Arr r (a, c) (b, c)
- 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
- data Eff r a
- qApp :: Arrs r b w -> b -> Eff r w
- qComp :: Arrs r a b -> (Eff r b -> Eff r' c) -> Arr r' a c
- send :: Member t r => t v -> Eff r v
- run :: Eff '[] w -> w
- handle_relay :: (a -> Eff r w) -> (forall v. t v -> Arr r v w -> Eff r w) -> Eff (t ': r) a -> Eff r w
- handle_relay_s :: s -> (s -> a -> Eff r w) -> (forall v. s -> t v -> (s -> Arr r v w) -> Eff r w) -> Eff (t ': r) a -> Eff r w
- interpose :: Member t r => (a -> Eff r w) -> (forall v. t v -> Arr r v w -> Eff r w) -> Eff r a -> Eff r w
Documentation
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
type Arrs r a b = FTCQueue (Eff r) a b Source #
An effectful function from a
to b
that is a composition
of several effectful functions. The paremeter r describes the overall
effect.
The composition members are accumulated in a type-aligned queue
The Eff monad (not a transformer!). It is a fairly standard coroutine monad
where the type r
is the type of effects that can be handled, and the
missing type a
(from the type application) is the type of value that is
returned. It is NOT a Free monad! There are no Functor constraints.
The two constructors denote the status of a coroutine (client): done with the
value of type a, or sending a request of type Union r with the continuation
Arrs r b a. Expressed another way: an Eff
can either be a value (i.e.,
Val
case), or an effect of type
producing another Union
rEff
(i.e.,
E
case). The result is that an Eff
can produce an arbitrarily long chain
of
effects, terminated with a pure value.Union
r
Potentially, inline Union into E
qApp :: Arrs r b w -> b -> Eff r w Source #
Application to the `generalized effectful function' Arrs r b w
qComp :: Arrs r a b -> (Eff r b -> Eff r' c) -> Arr r' a c Source #
Compose effectful arrows (and possibly change the effect!)
send :: Member t r => t v -> Eff r v Source #
Send a request and wait for a reply (resulting in an effectful computation).
run :: Eff '[] w -> w Source #
The initial case, no effects. Get the result from a pure computation.
The type of run ensures that all effects must be handled: only pure computations may be run.
handle_relay :: (a -> Eff r w) -> (forall v. t v -> Arr r v w -> Eff r w) -> Eff (t ': r) a -> Eff r w Source #
A convenient pattern: given a request (open union), either handle it or relay it.
handle_relay_s :: s -> (s -> a -> Eff r w) -> (forall v. s -> t v -> (s -> Arr r v w) -> Eff r w) -> Eff (t ': r) a -> Eff r w Source #
Parameterized handle_relay
interpose :: Member t r => (a -> Eff r w) -> (forall v. t v -> Arr r v w -> Eff r w) -> Eff r a -> Eff r w Source #
Add something like Control.Exception.catches? It could be useful for control with cut.
Intercept the request and possibly reply to it, but leave it unhandled (that's why we use the same r all throuout)