transformers-eff-0.1.0.0: An approach to managing composable effects, ala mtl/transformers/extensible-effects/Eff

Safe HaskellNone
LanguageHaskell2010

Control.Effect

Contents

Synopsis

Core API

newtype Eff f m a Source

The Eff monad transformer is used to write programs that require access to specific effects. In this library, effects are combined by stacking multiple Effs together, just as you would do with traditional monad transformers. Effs are parameterized by an effect algebra. This is a description of programs in a single effect, such as non-determinism ([])or exceptions (Either e). As Eff is a monad transformer, m is the monad that Eff transforms, which can itself be another instance of Eff.

Constructors

Eff (forall g r. (forall x. Sum f m x -> Cont (g r) x) -> Cont (g r) a) 

Instances

translate :: (Monad m, Monad (t m), MonadTrans t) => (forall x r. f x -> ContT r (t m) x) -> Eff f m a -> t m a Source

In order to run Eff computations, we need to provide a way to run its effects in a specific monad transformer. Notice that run eliminates one layer of Eff, returning you with the original a now captured under the result of the effects described by the effect functor.

class (IsEff m, Monad m) => Interprets p m | m -> p where Source

LiftProgram defines an mtl-style type class for automatically lifting effects into Eff stacks. When exporting libraries that you intend to publish on Hackage, it's suggested that you still provide your own type class (such as MonadThrow or MonadHTTP) to avoid locking people into this library, but interpret can be useful to define your own instances of that type class for Eff.

Methods

interpret :: p a -> m a Source

Instances

(Monad m, Interprets f (Eff h m)) => Interprets f (Eff g (Eff h m)) Source 
Monad m => Interprets f (Eff f m) Source 

type family IsEff m :: Constraint Source

The IsEff type family is used to make sure that a given monad stack is based around Eff. This is important, as it allows us to reason about Eff-based type classes, knowing that only Eff implements them, thus giving us the orthogonal-handling properties that we desire.

Equations

IsEff (Eff f m) = ()