effect-handlers-0.1.0.7: A library for writing extensible algebraic effects and handlers. Similar to extensible-effects but with deep handlers.

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Eff

Description

This implementation of the effect monad uses Free over a Union of functors and then applies Codensity over it for asymptotic improvements of ill-associated binds.

Synopsis

Documentation

data Eff r a Source

type Handler e r a b = Comp e r a b -> Res r b Source

Handler is a function that takes a result or an effect and a continuation |and handles it.

e is the effect functor you are handling

r represents the type of the type list of the remaining effects. Usually you want to be polymorphic in this.

a is the result type of the program you will handle

b is the result of handled computation.

data Comp e r a b Source

Comp represents a computation. It is either a pure value or a computation that needs further evaluation and effect handling.

Constructors

Value a 
Comp (e (Res r b)) 

type Res r = Free (Union r) Source

Result structure of the program is directly Free over Union indexed by the list of effect functors.

effect :: (forall b. (a -> Res r b) -> Union r (Res r b)) -> Eff r a Source

effect is meant to be used as a helper function for defining new effects. See predefined effects for examples. Good way to use it is to pass in a lambda expression with explicit k for continuation. You will need to manually inj into the Union because of some GHC limitations.

runPure :: Eff `[]` a -> a Source

A program without effects is guaranteed to be pure so you can safely convert it into a value.

runPureRes :: Res `[]` a -> a Source

Like runPure but for program results. You only need this for implementing some handlers.

handle :: (Functor e, Typeable e) => Handler e r a b -> Eff (e : r) a -> Eff r b Source

Use a Handler on an Eff program to stripe away the first layer of effects. There are some issues if you are using a handler that is somewhat polymorphic in e As the compiler cannot figure out which effect are you handling. Currently the best solution seems to be to manually specify type of the handler such that it is monomorphic in e. Sorry.

continue :: Res r a -> Eff r a Source

Convert a result back into a program in order to compose it. This function might not be needed and might introduce some performance issues (it is used in handle) but we didn't find a way to drop it.

finish :: Eff r a -> Res r a Source

Finish a program and convert it into a result structure.

inj :: (Typeable f, Functor f, Member f r) => f a -> Union r a Source

Smart constructor for Union. Injects the functor into any union of which the said functor is a member. Please note that only the type constructor need be a Typeable.

class Member f r Source

The Member type clas denotes that f is a member of type list r

Instances

Member x t => Member x ((:) (* -> *) h t) Source 
Member h ((:) (* -> *) h t) Source 

class Typeable a

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#