extensible-effects-2.3.0.0: An Alternative to Monad Transformers

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Eff

Description

A monadic library for communication between a handler and its client, the administered computation

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

Extensible Effects are implemented as typeclass constraints on an Eff[ect] datatype. A contrived example can be found under Control.Eff.Example. To run the effects, consult the tests.

Synopsis

Documentation

type Arr r a b = a -> Eff r b Source #

Effectful arrow type: a function from a to b that also does effects denoted by r

newtype Arrs r a b Source #

An effectful function from a to b that is a composition of one or more effectful functions. The paremeter r describes the overall effect.

The composition members are accumulated in a type-aligned queue. Using a newtype here enables us to define Category and Arrow instances.

Constructors

Arrs (FTCQueue (Eff r) a b) 

Instances

Arrow (Arrs r) Source #

As the name suggests, Arrs also has an Arrow instance.

Methods

arr :: (b -> c) -> Arrs r b c #

first :: Arrs r b c -> Arrs r (b, d) (c, d) #

second :: Arrs r b c -> Arrs r (d, b) (d, c) #

(***) :: Arrs r b c -> Arrs r b' c' -> Arrs r (b, b') (c, c') #

(&&&) :: Arrs r b c -> Arrs r b c' -> Arrs r b (c, c') #

Category * (Arrs r) Source #

Arrs can be composed and have a natural identity.

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

first :: Arr r a b -> Arr r (a, c) (b, c) Source #

singleK :: Arr r a b -> Arrs r a b Source #

convert single effectful arrow into composable type. i.e., convert Arr to Arrs

qApp :: forall r b w. Arrs r b w -> Arr r b w Source #

Application to the `generalized effectful function' Arrs r b w, i.e., convert Arrs to Arr

(^$) :: forall r b w. Arrs r b w -> Arr r b w Source #

Syntactic sugar for qApp

arr :: (a -> b) -> Arrs r a b Source #

Lift a function to an arrow

ident :: Arrs r a a Source #

The identity arrow

comp :: Arrs r a b -> Arrs r b c -> Arrs r a c Source #

Arrow composition

(^|>) :: Arrs r a b -> Arr r b c -> Arrs r a c Source #

Common pattern: append Arr to Arrs

data Eff r a Source #

The Eff monad (not a transformer!). It is a fairly standard coroutine monad 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. It is NOT a Free monad! There are no Functor constraints.

The two constructors denote the status of a coroutine (client): done with the value of type a, or sending a request of type Union r with the continuation Arrs r b a. Expressed another way: an Eff can either be a value (i.e., Val case), or an effect of type Union r producing another Eff (i.e., E case). The result is that an Eff can produce an arbitrarily long chain of Union r effects, terminated with a pure value.

Potentially, inline Union into E

Constructors

Val a 
E (Union r b) (Arrs r b a) 

Instances

Monad (Eff r) Source # 

Methods

(>>=) :: Eff r a -> (a -> Eff r b) -> Eff r b #

(>>) :: Eff r a -> Eff r b -> Eff r b #

return :: a -> Eff r a #

fail :: String -> Eff r a #

Functor (Eff r) Source #

Eff is still a monad and a functor (and Applicative) (despite the lack of the Functor constraint)

Methods

fmap :: (a -> b) -> Eff r a -> Eff r b #

(<$) :: a -> Eff r b -> Eff r a #

Applicative (Eff r) Source # 

Methods

pure :: a -> Eff r a #

(<*>) :: Eff r (a -> b) -> Eff r a -> Eff r b #

liftA2 :: (a -> b -> c) -> Eff r a -> Eff r b -> Eff r c #

(*>) :: Eff r a -> Eff r b -> Eff r b #

(<*) :: Eff r a -> Eff r b -> Eff r a #

qComp :: Arrs r a b -> (Eff r b -> Eff r' c) -> Arr r' a c Source #

Compose effectful arrows (and possibly change the effect!)

qComps :: Arrs r a b -> (Eff r b -> Eff r' c) -> Arrs r' a c Source #

Compose effectful arrows (and possibly change the effect!)

send :: Member t r => t v -> Eff r v Source #

Send a request and wait for a reply (resulting in an effectful computation).

run :: Eff '[] w -> w Source #

The initial case, no effects. Get the result from a pure computation.

The type of run ensures that all effects must be handled: only pure computations may be run.

handle_relay :: (a -> Eff r w) -> (forall v. t v -> Arr r v w -> Eff r w) -> Eff (t ': r) a -> Eff r w Source #

A convenient pattern: given a request (open union), either handle it or relay it.

handle_relay_s :: s -> (s -> a -> Eff r w) -> (forall v. s -> t v -> (s -> Arr r v w) -> Eff r w) -> Eff (t ': r) a -> Eff r w Source #

Parameterized handle_relay

interpose :: Member t r => (a -> Eff r w) -> (forall v. t v -> Arr r v w -> Eff r w) -> Eff r a -> Eff r w Source #

Add something like Control.Exception.catches? It could be useful for control with cut.

Intercept the request and possibly reply to it, but leave it unhandled (that's why we use the same r all throuout)