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

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Effect

Contents

Synopsis

The Effect Monad

data Effect l a

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

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

Instances

(Member (* -> *) (Exception e) l, (~) (* -> *) (Exception e) (InstanceOf (* -> * -> *) Exception l)) => MonadError e (Effect l) 
(Member (* -> *) (Reader r) l, (~) (* -> *) (Reader r) (InstanceOf (* -> * -> *) Reader l)) => MonadReader r (Effect l) 
(Member (* -> *) (State s) l, (~) (* -> *) (State s) (InstanceOf (* -> * -> *) State l)) => MonadState s (Effect l) 
(Monoid w, Member (* -> *) (Writer w) l, (~) (* -> *) (Writer w) (InstanceOf (* -> * -> *) Writer l)) => MonadWriter w (Effect l) 
Effectful l (Effect l a) 
EffectList l => Alternative (Effect l) 
Monad (Effect l) 
Functor (Effect l) 
EffectList l => MonadPlus (Effect l) 
Applicative (Effect l) 
EffectLift IO l => MonadIO (Effect l) 
type EffectsOf (Effect l a) = l 

runEffect :: Effect Nil a -> a

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

send :: (Functor f, Member f l) => f a -> Effect l a

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

sendEffect :: (Functor f, Member f l, Effectful l r) => f r -> r

Executes an effect of type f that produces a return value of type r. Note that a specific instance of this function is of type (Functor f, Member f l) => f (Effect l a) -> Effect l a, which allows users to send effects parameterized by effects.

Effect Handlers

class (l ~ EffectsOf r) => Effectful l r

The class of types which result in an effect. That is:

Effect l r
a -> Effect l r
a -> b -> Effect l r
...

Associated Types

type EffectsOf r :: Row (* -> *)

Determines the effects associated with the return type of a function.

Instances

Effectful l r => Effectful l (a -> r) 
Effectful l (Effect l a) 

eliminate :: Effectful l r => (a -> r) -> (f r -> r) -> Effect (f :+ l) a -> r

Completely handles an effect. The given function is passed an effect value parameterized by the output type (i.e. the return type of handle).

The most common instantiation of this function is:

(a -> Effect l b) -> (f (Effect l b) -> Effect l b) -> Effect (f ': l) a -> Effect l b

intercept :: (Effectful l r, Member f l) => (a -> r) -> (f r -> r) -> Effect l a -> r

Handles 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).

The most common instantiation of this function is:

(a -> Effect l b) -> (f (Effect l b) -> Effect l b) -> Effect l a -> Effect l b

extend :: Effect l a -> Effect (f :+ l) a

Adds an arbitrary effect to the head of the effect list.

enable :: Effect (f :- l) a -> Effect l a

Enables an effect that was previously disabled.

conceal :: Member f l => Effect (f :+ l) a -> Effect l a

Hides an effect g by translating each instance of g into an instance of another effect f.

reveal :: Member f l => Effect l a -> Effect (f :+ l) a

Hides an effect g by translating each instance of another effect f into an instance of g.

rename :: Functor g => (forall r. f r -> g r) -> Effect (f :+ l) a -> Effect (g :+ l) a

Translates the first effect in the effect list into another effect.

swap :: Effect (f :+ (g :+ l)) a -> Effect (g :+ (f :+ l)) a

Reorders the first two effects in a computation.

rotate :: Effect (f :+ (g :+ (h :+ l))) a -> Effect (g :+ (h :+ (f :+ l))) a

Rotates the first three effects in a computation.

mask :: (Functor f, KnownLength l, Member f m) => (forall r. Union l r -> f r) -> Effect (l :++ m) a -> Effect m a

Converts a set of effects l into a single effect f.

 mask f = conceal . rename f . unflatten

unmask :: (Functor f, Inclusive l, Member f m) => (forall r. f r -> Union l r) -> Effect m a -> Effect (l :++ m) a

Converts an effect f into a set of effects l.

 unmask f = flatten . rename f . reveal

Unions

data Union l a

Represents a union of the list of type constructors in l parameterized by a. As an effect, it represents the union of each type constructor's corresponding effect. From the user's perspective, it provides a way to encapsulate multiple effects.

Instances

flatten :: Inclusive l => Effect (Union l :+ m) a -> Effect (l :++ m) a

Distributes the sub-effects of a Union effect across a computation.

unflatten :: KnownLength l => Effect (l :++ m) a -> Effect (Union l :+ m) a

Collects some effects in a computation into a Union effect.

Membership

class KnownNat (IndexOf e l) => Member e l

A constraint specifying that e is a member of the Row l.

Instances

KnownNat (IndexOf k e l) => Member k e l 

class (Member f l, f ~ InstanceOf name l) => MemberEffect name f l

A refined Membership constraint that can infer f from l, given name. In order for this to be used, Is name f must be defined. For example:

data Reader r a = ...

type instance Is Reader f = IsReader f

type IsReader f where
    IsReader (Reader r) = True
    IsReader f = False

type ReaderEffect r l = MemberEffect Reader (Reader r) l

ask :: ReaderEffect r l => Effect l r
ask = ...

Given the constraint ReaderEffect r l in the above example, r can be inferred from l.

Instances

(Member (* -> *) f l, (~) (* -> *) f (InstanceOf k name l)) => MemberEffect k name f l 

type family Is name f :: Bool

Returns a boolean value indicating whether f belongs to the group of effects identified by name. This allows MemberEffect to infer the associated types for arbitrary effects.

Instances

type Is ((* -> *) -> * -> *) Lift f 
type Is (* -> * -> * -> *) Coroutine f 
type Is (* -> * -> *) Witness f 
type Is (* -> * -> *) State f 
type Is (* -> * -> *) Writer f 
type Is (* -> * -> *) Reader f 
type Is (* -> * -> *) Bracket f 
type Is (* -> * -> *) Exception f 
type Is (* -> *) List f 

Effect Rows

data Row a

A type level list with explicit removals.

Constructors

Nil

The empty list.

a :+ (Row a) infixr 5

Prepends an element (cons).

a :- (Row a) infixr 5

Deletes the first instance an element.

type family l :++ m infixr 5

Appends two type level Rows.

Equations

Nil :++ l = l 
(e :+ l) :++ m = e :+ (l :++ m) 
(e :- l) :++ m = e :- (l :++ m) 

class KnownNat (Length l) => KnownLength l

The class of Rows with statically known lengths.

Instances

KnownNat (Length k l) => KnownLength k l 

class KnownLength l => Inclusive l

The class of Rows that do not contain deletions (:-).

Instances

Inclusive k (Nil k) 
Inclusive k l => Inclusive k ((:+) k e l)