Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module lets you handle effects using an effectful program using a model of two communicating processes.
- The
normal
computation: a computation that uses some effectf
and possibly others effects,r
- The handling computation: a computation that responds to the
effects
f
of the normal computation by means ofConverse f
and is also allowed to use the effectsr
.
This effect is called Converse
, because it is meaningful both as a verb and as an adjective.
- The computations converse — having a one-to-one conversation where
f
is the language - The handling computation has perform the opposite/converse of
the normal computation: when the normal computation requests a
value by means of
f
and the handler emits aConverse f
effect, the handler has to provide that value.
- runConverse :: Eff (f ': r) v -> Eff (Converse f r v ': r) b -> Eff r b
- data Converse f r v a
- converse :: (forall x. f x -> Eff r (Maybe x, b)) -> (v -> Eff r b) -> Eff (Converse f r v ': r) b
- peekEvent :: (forall x. f x -> Eff r a) -> Eff (Converse f r v ': r) (Either v a)
- showNext :: (Show v, ShowP f) => Eff (Converse f r v ': r) String
- module Control.Monad.Freer
Running tests
:: Eff (f ': r) v | The normal computation |
-> Eff (Converse f r v ': r) b | The handling computation |
-> Eff r b | A runnable combined computation |
Zips together the two communicating computations, the normal computation
that uses effect f
and the handling computation that uses effect Converse f
The handling computation gets to run effects (the r
parameter) first
whenever a scheduling
choice presents itself.
data Converse f r v a Source #
Handle the effects of another computation, as an effect.
For example, a handling computation may have type Eff '[Converse f m v] a
and handles effects for the normal
computation Eff '[f] v
.
Type parameters:
f
- The effect that is communicated between the normal computation and the handling computation
r
- The remaining effects that both computations may use
v
- The result of the normal computation
a
- The result of the handling computation
:: (forall x. f x -> Eff r (Maybe x, b)) | Handle an effect emitted by the normal computation. This may produce other effects in |
-> (v -> Eff r b) | Handle the case where the normal computation has completed and returned a value of type |
-> Eff (Converse f r v ': r) b | A computation that should run in the handling computation. |
Called by the handling computation, to interact with the normal
computation. (See module description for definitions)
This is the most general way of interacting with the normal computation, reflecting the constructor of the Converse
type.
peekEvent :: (forall x. f x -> Eff r a) -> Eff (Converse f r v ': r) (Either v a) Source #
Look at the next event without handling it
showNext :: (Show v, ShowP f) => Eff (Converse f r v ': r) String Source #
Show what happens next, examples:
"Next event: ReadLine"
"Done with result: 42"
module Control.Monad.Freer