| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Eff
Contents
Description
A monadic library for implementing effectful computation in a modular way.
This module provides the Eff monad - the base type for all effectful
computation.
The Member typeclass is the main interface for describing which effects
are necessary for a given function.
Consult the Control.Eff.QuickStart module and the readme for gentle
introductions.
To use extensible effects effectively some language extensions are necessary/recommended.
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MonoLocalBinds #-}
Effect base-type
run :: Eff '[] w -> w Source #
Get the result from a pure (i.e. no effects) computation.
The type of run ensures that all effects must be handled: only pure computations can be run.
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
Instances
| (MonadBase b m, SetMember (* -> *) (Lift *) (Lift * m) r) => MonadBase b (Eff r) Source # | |
| MonadBase m m => MonadBaseControl m (Eff ((:) (* -> *) (Lift * m) ([] (* -> *)))) Source # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) (Writer w) r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) (Writer w) r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) s, MonadBaseControl m (Eff s)) => MonadBaseControl m (Eff ((:) (* -> *) (Reader * e) s)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) (State s) r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) s, MonadBaseControl m (Eff s)) => MonadBaseControl m (Eff ((:) (* -> *) (Reader * e) s)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) (OnDemandState s) r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) (State s) r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) NdetEff r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) Fresh r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) (Exc * e) r)) # | |
| (MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) Choose r)) # | |
| Monad (Eff r) Source # | |
| Functor (Eff r) Source # | Eff is still a monad and a functor (and Applicative) (despite the lack of the Functor constraint) |
| Applicative (Eff r) Source # | |
| (MonadIO m, SetMember (* -> *) (Lift *) (Lift * m) r) => MonadIO (Eff r) Source # | |
| type StM (Eff ((:) (* -> *) (Lift * m) ([] (* -> *)))) a Source # | |
| type StM (Eff ((:) (* -> *) (Writer w) r)) a # | |
| type StM (Eff ((:) (* -> *) (Writer w) r)) a # | |
| type StM (Eff ((:) (* -> *) (State s) r)) a # | |
| type StM (Eff ((:) (* -> *) (OnDemandState s) r)) a # | |
| type StM (Eff ((:) (* -> *) (State s) r)) a # | |
| type StM (Eff ((:) (* -> *) NdetEff r)) a # | |
| type StM (Eff ((:) (* -> *) Fresh r)) a # | |
| type StM (Eff ((:) (* -> *) Choose r)) a # | |
| type StM (Eff ((:) (* -> *) (Reader * e) s)) a # | |
| type StM (Eff ((:) (* -> *) (Reader * e) s)) a # | |
| type StM (Eff ((:) (* -> *) (Exc * e) r)) a # | |
Effect list
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 necessary for implementation reasons and is not
required for using the effect list.
Instances
| FindElem [* -> *] t r => Member t r Source # | |
| (~) (* -> *) t s => Member t ((:) (* -> *) s ([] (* -> *))) 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 |
class Member t r => SetMember (tag :: k -> * -> *) (t :: * -> *) r | tag r -> t Source #
This class is used for emulating monad transformers
type family (ms :: [* -> *]) <:: r where ... Source #
A useful operator for reducing boilerplate.
f :: [Reader Int, Writer String] <:: r => a -> Eff r b
is equal to
f :: (Member (Reader Int) r, Member (Writer String) r) => a -> Eff r b
Equations
| '[] <:: r = (() :: Constraint) | |
| (m ': ms) <:: r = (Member m r, (<::) ms r) |