extensible-effects-1.0

Safe HaskellNone

Control.Eff

Description

Original work available at: http:okmij.orgftpHgetellextensibleEff.hs. This module implements extensible effects as an alternative to monad transformers, as described in http:okmij.orgftpHgetellextensibleexteff.pdf.

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

  • - Print a list of numbers, then print their sum. printAndSum :: (Member (Lift IO) e, Member State e) => [Integer] -> Eff e Integer printAndSum (x:xs) = do lift $ putStrLn $ show x onState (+ x) printAndSum [] = getState >>= lift . putStrLn

Synopsis

Documentation

data Eff r a Source

Instances

class Member t r Source

Instances

Member t r => Member t (:> t' r) 
Member t (:> t r) 

data a :> b Source

A sum data type, for composing effects In GHC 7.4, we should make it a list (:>) :: (* -> *) -> (* -> List) -> List

Instances

Member t r => Member t (:> t' r) 
Member t (:> t r) 

run :: Eff Void w -> wSource

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

admin :: Eff r w -> VE w rSource

data Reader e v Source

The request for a value of type e from the current environment. This environment is analogous to a parameter of type e.

Instances

runReader :: Typeable e => Eff (Reader e :> r) w -> e -> Eff r wSource

The handler of Reader requests. The return type shows that all Reader requests are fully handled.

local :: (Typeable e, Member (Reader e) r) => (e -> e) -> Eff r a -> Eff r aSource

Locally rebind the value in the dynamic environment. This function both requests and admins Reader requests.

runTrace :: Eff (Trace :> Void) w -> IO wSource

data Yield a v Source

The yield request: reporting the value of type e and suspending the coroutine (For simplicity, a co-routine reports a value but accepts unit)

Instances

yield :: (Typeable a, Member (Yield a) r) => a -> Eff r ()Source

runC :: Typeable a => Eff (Yield a :> r) w -> Eff r (Y r a)Source

Launch a thread and report its status.

data Y r a Source

Status of a thread: done or reporting the value of the type a (For simplicity, a co-routine reports a value but accepts unit)

Constructors

Done 
Y a (() -> Eff r (Y r a)) 

data State s w Source

Strict state. Example: Implementing Fresh in terms of State but not revealing that fact. runFresh' :: (Typeable i, Enum i, Num i) => Eff (Fresh i :> r) w -> i -> Eff r w runFresh' m s = fst $ runState s (loop $ admin m) where loop (Val x) = return x loop (E u) = case decomp u of Right (Fresh k) -> do n <- getState putState (n + 1) loop (k n) Left u' -> send (k -> unsafeReUnion $ k $ u') >>= loop

Instances

getState :: Typeable e => Member (State e) r => Eff r eSource

putState :: Typeable e => Member (State e) r => e -> Eff r ()Source

onState :: (Typeable s, Member (State s) r) => (s -> s) -> Eff r ()Source

runState :: Typeable s => s -> Eff (State s :> r) w -> Eff r (w, s)Source

choose :: Member Choose r => [a] -> Eff r aSource

runChoice :: forall a r. Eff (Choose :> r) a -> Eff r [a]Source

data Lift m v Source

Instances

lift :: (Typeable1 m, Member (Lift m) r) => m a -> Eff r aSource

Lift a Monad to an Effect.

runLift :: (Monad m, Typeable1 m) => Eff (Lift m :> Void) w -> m wSource

The handler of Lift requests. It is meant to be terminal: we only allow a single Lifted Monad because Monads aren't commutative (e.g. Maybe (IO a) is functionally different from IO (Maybe a)).

data Exc e v Source

Instances

throwError :: (Typeable e, Member (Exc e) r) => e -> Eff r aSource

runError :: Typeable e => Eff (Exc e :> r) a -> Eff r (Either e a)Source

catchError :: (Typeable e, Member (Exc e) r) => Eff r a -> (e -> Eff r a) -> Eff r aSource

data Fresh i v Source

Instances

fresh :: (Typeable i, Enum i, Member (Fresh i) r) => Eff r iSource

runFresh :: (Typeable i, Enum i) => Eff (Fresh i :> r) w -> i -> Eff r wSource

call :: Member Choose r => Eff (Exc CutFalse :> r) a -> Eff r aSource