effin-0.1.0.0: A Typeable-free implementation of extensible effects

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Effect

Contents

Description

This module provides three things:

  1. An Effect monad for representing effectful computations,
  2. A DSL for effect handling that lets you cleanly handle an arbitrary number of effects, and
  3. A type-level list membership constraint.

Synopsis

The Effect Monad

data Effect es a Source

An effectful computation. An Effect es a may perform any of the effects specified by the list of effects es before returning a result of type a. The definition is isomorphic to the following GADT:

data Effect es a where
    Done :: a -> Effect es a
    Side :: `Union` es (Effect es a) -> Effect es a

Instances

EffectException e es => MonadError e (Effect es) 
EffectReader r es => MonadReader r (Effect es) 
EffectState s es => MonadState s (Effect es) 
EffectWriter e es => MonadWriter e (Effect es) 
EffectList es => Alternative (Effect es) 
Monad (Effect es) 
Functor (Effect es) 
EffectList es => MonadPlus (Effect es) 
Applicative (Effect es) 
EffectLift IO es => MonadIO (Effect es) 

runEffect :: Effect [] a -> a Source

Converts an computation that produces no effects into a regular value.

send :: Member e es => e a -> Effect es a Source

Executes an effect of type e that produces a return value of type a.

sendEffect :: Member e es => e (Effect es a) -> Effect es a Source

Executes an effect of type e that produces a return value of type a.

Effect Handlers

The following types and functions form a small DSL that allows users to specify how to handle effects. A handler can be formed by a call to handle, followed by a chain of calls to eliminate, intercept, and ended by either a defaultRelay, emptyRelay, or a call to relay.

For example, a possible handler for the state effect would be:

data State s a = State (s -> (s, a))

runState :: Effect (State s ': es) a -> s -> Effect es (s, a)
runState =
    handle (\output state -> return (state, output))
    $ eliminate (\(State transform) state ->
        let (state', continue) = transform state
        in continue state')
    $ relay (\effect state -> do
        continue <- sendEffect effect
        return (continue state))

As an analogy to monads, handle lets you specify the return function, while eliminate, intercept, and relay, let you specify the bind function.

data Handler es a Source

A handler for an effectful computation. Combined with handle, allows one to convert a computation parameterized by the effect list es to a value of type a.

handle :: (a -> b) -> Handler es b -> Effect es a -> b Source

handle p h transforms an effect into a value of type b.

p specifies how to convert pure values. That is,

handle p h (return x) = p x

h specifies how to handle effects.

eliminate :: (e b -> b) -> Handler es b -> Handler (e : es) b Source

Provides a way to completely handle an effect. The given function is passed an effect value parameterized by the output type (i.e. the return type of handle).

intercept :: Member e es => (e b -> b) -> Handler es b -> Handler es b Source

Provides a way to handle an effect without eliminating it. The given function is passed an effect value parameterized by the output type (i.e. the return type of handle).

relay :: (forall e. Member e es => e b -> b) -> Handler es b Source

Computes a basis handler. Provides a way to pass on effects of unknown types. In most cases, defaultRelay is sufficient.

defaultRelay :: Handler es (Effect es a) Source

Relays all effects without examining them.

handle id defaultRelay x = x

emptyRelay :: Handler [] a Source

A handler for when there are no effects. Since Handlers handle effects, they cannot be run on a computation that never produces an effect. By the principle of explosion, a handler that requires exactly zero effects can produce any value.

Membership

class (Functor t, Member' t ts (IndexOf t ts)) => Member t ts Source

A constraint that requires that the type constructor t :: * -> * is a member of the list of types ts :: [* -> *].

Minimal complete definition

index

Instances

(Functor t, Member' t ts (IndexOf t ts)) => Member t ts