extensible-effects-1.8.1.0: An Alternative to Monad Transformers

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Eff

Description

Original work available at http://okmij.org/ftp/Haskell/extensible/Eff.hs. This module implements extensible effects as an alternative to monad transformers, as described in http://okmij.org/ftp/Haskell/extensible/exteff.pdf.

Extensible Effects are implemented as typeclass constraints on an Eff[ect] datatype. A contrived example is:

{-# LANGUAGE FlexibleContexts #-}
import Control.Eff
import Control.Eff.Lift
import Control.Eff.State
import Control.Monad (void)
import Data.Typeable

-- Write the elements of a list of numbers, in order.
writeAll :: (Typeable a, Member (Writer a) e)
         => [a]
         -> Eff e ()
writeAll = mapM_ putWriter

-- Add a list of numbers to the current state.
sumAll :: (Typeable a, Num a, Member (State a) e)
       => [a]
       -> Eff e ()
sumAll = mapM_ (onState . (+))

-- Write a list of numbers and add them to the current state.
writeAndAdd :: (Member (Writer Integer) e, Member (State Integer) e)
            => [Integer]
            -> Eff e ()
writeAndAdd l = do
    writeAll l
    sumAll l

-- Sum a list of numbers.
sumEff :: (Num a, Typeable a) => [a] -> a
sumEff l = let (s, ()) = run $ runState 0 $ sumAll l
           in s

-- Safely get the last element of a list.
-- Nothing for empty lists; Just the last element otherwise.
lastEff :: Typeable a => [a] -> Maybe a
lastEff l = let (a, ()) = run $ runWriter $ writeAll l
            in a

-- Get the last element and sum of a list
lastAndSum :: (Typeable a, Num a) => [a] -> (Maybe a, a)
lastAndSum l = let (lst, (total, ())) = run $ runWriter $ runState 0 $ writeAndAdd l
               in (lst, total)

Synopsis

Documentation

type Eff r = Codensity (VE r) Source

Basic datatype returned by all computations with extensible effects. The Eff r type is a type synonym 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.

As is made explicit below, the Eff type is simply the application of the Codensity transformer to VE:

type Eff r a = Codensity (VE r) a

This is done to gain the asymptotic speedups for scenarios where there is a single execution stage where the built up monadic computation gets executed. For scenarios where the computation execution and building stages are interspersed, the reflection without remorse techniques would be a better fit. See https://github.com/atzeus/reflectionwithoutremorse.

type VE r = Free (Union r) Source

A VE is either a value, or an effect of type Union r producing another VE. The result is that a VE can produce an arbitrarily long chain of Union r effects, terminated with a pure value.

As is made explicit here, VE is simply the Free monad resulting from the Union r functor.

data Free f a :: (* -> *) -> * -> *

The Free Monad for a Functor f.

Formally

A Monad n is a free Monad for f if every monad homomorphism from n to another monad m is equivalent to a natural transformation from f to m.

Why Free?

Every "free" functor is left adjoint to some "forgetful" functor.

If we define a forgetful functor U from the category of monads to the category of functors that just forgets the Monad, leaving only the Functor. i.e.

U (M,return,join) = M

then Free is the left adjoint to U.

Being Free being left adjoint to U means that there is an isomorphism between

Free f -> m in the category of monads and f -> U m in the category of functors.

Morphisms in the category of monads are Monad homomorphisms (natural transformations that respect return and join).

Morphisms in the category of functors are Functor homomorphisms (natural transformations).

Given this isomorphism, every monad homomorphism from Free f to m is equivalent to a natural transformation from f to m

Showing that this isomorphism holds is left as an exercise.

In practice, you can just view a Free f a as many layers of f wrapped around values of type a, where (>>=) performs substitution and grafts new layers of f in for each of the free variables.

This can be very useful for modeling domain specific languages, trees, or other constructs.

This instance of MonadFree is fairly naive about the encoding. For more efficient free monad implementation see Control.Monad.Free.Church, in particular note the improve combinator. You may also want to take a look at the kan-extensions package (http://hackage.haskell.org/package/kan-extensions).

A number of common monads arise as free monads,

  • Given data Empty a, Free Empty is isomorphic to the Identity monad.
  • Free Maybe can be used to model a partiality monad where each layer represents running the computation for a while longer.

Constructors

Pure a 
Free (f (Free f a)) 

Instances

MonadTrans Free

This is not a true monad transformer. It is only a monad transformer "up to retract".

(Functor m, MonadState s m) => MonadState s (Free m) 
(Functor m, MonadReader e m) => MonadReader e (Free m) 
Functor f => MonadFree f (Free f) 
(Functor m, MonadError e m) => MonadError e (Free m) 
(Functor m, MonadWriter e m) => MonadWriter e (Free m) 
(MonadBase b m, Typeable (* -> *) m, SetMember ((* -> *) -> * -> *) Lift (Lift m) r) => MonadBase b (Eff r) 
Alternative v => Alternative (Free v)

This violates the Alternative laws, handle with care.

Functor f => Monad (Free f) 
Functor f => Functor (Free f) 
Functor f => MonadFix (Free f) 
(Functor v, MonadPlus v) => MonadPlus (Free v)

This violates the MonadPlus laws, handle with care.

Functor f => Applicative (Free f) 
Foldable f => Foldable (Free f) 
Traversable f => Traversable (Free f) 
(Typeable (* -> *) m, MonadIO m, SetMember ((* -> *) -> * -> *) Lift (Lift m) r) => MonadIO (Eff r) 
(Functor m, MonadCont m) => MonadCont (Free m) 
(Functor f, Eq1 f) => Eq1 (Free f) 
(Functor f, Ord1 f) => Ord1 (Free f) 
(Functor f, Show1 f) => Show1 (Free f) 
(Functor f, Read1 f) => Read1 (Free f) 
Traversable1 f => Traversable1 (Free f) 
Foldable1 f => Foldable1 (Free f) 
Functor f => Apply (Free f) 
Functor f => Bind (Free f) 
(Eq (f (Free f a)), Eq a) => Eq (Free f a) 
(Ord (f (Free f a)), Ord a) => Ord (Free f a) 
(Read (f (Free f a)), Read a) => Read (Free f a) 
(Show (f (Free f a)), Show a) => Show (Free f a) 
Typeable ((* -> *) -> * -> *) Free 

class (Member' t r ~ True) => Member t r Source

Class Member is defined only for the sake of the interface compatibility with OpenUnion1. Generally, the closed type family Member' below could be used instead.

The Member t r specifies whether t is present anywhere in the sum type r, where t is some effectful type, e.g. Lift IO, State Int`.

Instances

(~) Bool (Member' t r) True => Member t r 

class Member t r => SetMember set t r | r set -> t Source

SetMember is similar to Member, but it allows types to belong to a "set". For every set, only one member can be in r at any given time. This allows us to specify exclusivity and uniqueness among arbitrary effects:

-- Terminal effects (effects which must be run last)
data Terminal

-- Make Lifts part of the Terminal effects set.
-- The fundep assures that there can only be one Terminal effect for any r.
instance Member (Lift m) r => SetMember Terminal (Lift m) r

-- Only allow a single unique Lift effect, by making a "Lift" set.
instance Member (Lift m) r => SetMember Lift (Lift m) r

Instances

MemberU k set t r => SetMember (k -> * -> *) set t r 

data Union r v Source

Parameter r is phantom: it just tells what could be in the union. Where r is t1 :> t2 ... :> tn, Union r v can be constructed with a value of type ti v. Ideally, we should be able to add the constraint Member t r.

NOTE: exposing the constructor below allows users to bypass the type system. See unsafeReUnion for example.

Instances

(MonadBase b m, Typeable (* -> *) m, SetMember ((* -> *) -> * -> *) Lift (Lift m) r) => MonadBase b (Eff r) 
Functor (Union r) 
(Typeable (* -> *) m, MonadIO m, SetMember ((* -> *) -> * -> *) Lift (Lift m) r) => MonadIO (Eff r) 
Typeable (* -> * -> *) Union 

data a :> b infixr 1 Source

A sum data type, for composing effects

Instances

Typeable ((* -> *) -> * -> *) (:>) 

inj :: (Functor t, Typeable t, Member t r) => t v -> Union r v Source

Construct a Union.

prj :: (Typeable t, Member t r) => Union r v -> Maybe (t v) Source

Try extracting the contents of a Union as a given type.

prjForce :: (Typeable t, Member t r) => Union r v -> (t v -> a) -> a Source

Extract the contents of a Union as a given type. If the Union isn't of that type, a runtime error occurs.

decomp :: Typeable t => Union (t :> r) v -> Either (Union r v) (t v) Source

Try extracting the contents of a Union as a given type. If we can't, return a reduced Union that excludes the type we just checked.

send :: (forall w. (a -> VE r w) -> Union r (VE r w)) -> Eff r a Source

Given a method of turning requests into results, we produce an effectful computation.

admin :: Eff r w -> VE r w Source

Tell an effectful computation that you're ready to start running effects and return a value.

run :: Eff () w -> w Source

Get the result from a pure computation.

interpose :: (Typeable t, Functor t, Member t r) => Union r v -> (v -> Eff r a) -> (t v -> Eff r a) -> Eff r a Source

Given a request, either handle it or relay it. Both the handler and the relay can produce the same type of request that was handled.

handleRelay Source

Arguments

:: Typeable t 
=> Union (t :> r) v

Request

-> (v -> Eff r a)

Relay the request

-> (t v -> Eff r a)

Handle the request of type t

-> Eff r a 

Given a request, either handle it or relay it.

unsafeReUnion :: Union r w -> Union t w Source

Juggle types for a Union. Use cautiously.