freer-effects-0.3.0.0: Implementation of effect system for Haskell.

Copyright(c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.
LicenseBSD3
Maintainerixcom-core@ixperta.com
Stabilityexperimental
PortabilityGHC specific language extensions.
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Freer

Contents

Description

 

Synopsis

Effect Monad

data Eff effs a Source #

The Eff monad provides a way to use effects in Haskell, in such a way that different types of effects can be interleaved, and so that the produced code is efficient.

Instances

Monad (Eff effs) Source # 

Methods

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

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

return :: a -> Eff effs a #

fail :: String -> Eff effs a #

Functor (Eff effs) Source # 

Methods

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

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

Applicative (Eff effs) Source # 

Methods

pure :: a -> Eff effs a #

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

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

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

Member NonDet effs => Alternative (Eff effs) Source # 

Methods

empty :: Eff effs a #

(<|>) :: Eff effs a -> Eff effs a -> Eff effs a #

some :: Eff effs a -> Eff effs [a] #

many :: Eff effs a -> Eff effs [a] #

Member NonDet effs => MonadPlus (Eff effs) Source # 

Methods

mzero :: Eff effs a #

mplus :: Eff effs a -> Eff effs a -> Eff effs a #

Effect Constraints

class FindElem t r => Member t r Source #

This type class is used for two following purposes:

  • As a Constraint it guarantees that t :: * -> * is a member of a type-list r :: [* -> *].
  • Provides a way how to inject/project t :: * -> * into/from a Union, respectively.

Following law has to hold:

prj . inj === Just

Minimal complete definition

inj, prj

Instances

FindElem t r => Member t r Source # 

Methods

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

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

type family Members m r :: Constraint where ... Source #

Equations

Members (t ': c) r = (Member t r, Members c r) 
Members '[] r = () 

Sending Arbitrary Effect

send :: Member eff effs => eff a -> Eff effs a Source #

Send a request and wait for a reply.

Handling Effects

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

Effectful arrow type: a function from a :: * to b :: * that also does effects denoted by effs :: [* -> *].

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

Runs a set of Effects. Requires that all effects are consumed. Typically composed as follows:

run . runEff1 eff1Arg . runEff2 eff2Arg1 eff2Arg2 $ someProgram

runM :: Monad m => Eff '[m] a -> m a Source #

Runs a set of Effects. Requires that all effects are consumed, except for a single effect known to be a monad. The value returned is a computation in that monad. This is useful for plugging in traditional transformer stacks.

Building Effect Handlers

runNat :: Member m effs => (forall a. eff a -> m a) -> Eff (eff ': effs) b -> Eff effs b Source #

Variant of handleRelay simplified for the common case.

runNatS :: Member m effs => s -> (forall a. s -> eff a -> m (s, a)) -> Eff (eff ': effs) b -> Eff effs b Source #

Variant of handleRelayS simplified for the common case.

handleRelay Source #

Arguments

:: (a -> Eff effs b)

Handle a pure value.

-> (forall v. eff v -> Arr effs v b -> Eff effs b)

Handle a request for effect of type eff :: * -> *.

-> Eff (eff ': effs) a 
-> Eff effs b

Result with effects of type eff :: * -> * handled.

Given a request, either handle it or relay it.

handleRelayS Source #

Arguments

:: s 
-> (s -> a -> Eff effs b)

Handle a pure value.

-> (forall v. s -> eff v -> (s -> Arr effs v b) -> Eff effs b)

Handle a request for effect of type eff :: * -> *.

-> Eff (eff ': effs) a 
-> Eff effs b

Result with effects of type eff :: * -> * handled.

Parameterized handleRelay. Allows sending along some state of type s :: * to be handled for the target effect, or relayed to a handler that can- handle the target effect.