more-extensible-effects-0.1.0.4: Initial project template from stack

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Eff

Synopsis

Documentation

data Eff r a Source #

The Eff monad (not a transformer!) It is a fairly standard coroutine monad It is NOT a Free monad! There are no Functor constraints Status of a coroutine (client): done with the value of type w, or sending a request of type Union r with the continuation Arrs r b a. Potentially, inline Union into Impure

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 # 

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 #

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

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

class KnownNat (FindElem t r) => Member t r Source #

Minimal complete definition

inj, prj

Instances

KnownNat (FindElem t r) => Member t r Source # 

Methods

inj :: t v -> Union * r v Source #

prj :: Union * r v -> Maybe (t v) Source #

class Member t r => MemberU2 tag t r | tag r -> t Source #

Instances

MemberU' k (EQU (* -> *) t1 t2) tag t1 ((:) (* -> *) t2 r) => MemberU2 k tag t1 ((:) (* -> *) t2 r) Source # 

type Handler t r w = forall v. t v -> Arr r v w -> Eff r w Source #

Handler type

type HandlerS s t r w = forall v. s -> t v -> (s -> Arr r v w) -> Eff r w Source #

Parameterized Handler type

handleRelay :: (a -> Eff r w) -> Handler t r w -> Eff (t ': r) a -> Eff r w Source #

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

handleRelayS :: s -> (s -> a -> Eff r w) -> HandlerS s t r w -> Eff (t ': r) a -> Eff r w Source #

Parameterized handleRelay

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

send a request and wait for a reply

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 #

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

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