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.Internal

Contents

Description

Internal machinery for this effects library. This includes:

  • Eff data type, for expressing effects.
  • NonDet data type, for nondeterministic effects.
  • Functions for facilitating the construction of effects and their handlers.

Using http://okmij.org/ftp/Haskell/extensible/Eff1.hs as a starting point.

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.

Constructors

Val a

Pure value (return = pure = Val).

E (Union effs b) (Arrs effs b a)

Sending a request of type Union effs with the continuation Arrs r b a.

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 #

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 :: [* -> *].

type Arrs effs a b = FTCQueue (Eff effs) a b Source #

An effectful function from a :: * to b :: * that is a composition of several effectful functions. The paremeter eff :: [* -> *] describes the overall effect. The composition members are accumulated in a type-aligned queue.

Open Union

Open Union (type-indexed co-product) of effects.

Fast Type-aligned Queue

Fast type-aligned queue optimized to effectful functions of type (a -> m b).

Sending Arbitrary Effect

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

Send a request and wait for a reply.

Handling Effects

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

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.

interpose :: Member eff effs => (a -> Eff effs b) -> (forall v. eff v -> Arr effs v b -> Eff effs b) -> Eff effs a -> Eff effs b Source #

Intercept the request and possibly reply to it, but leave it unhandled.

Low-level Functions for Building Effect Handlers

qApp :: Arrs effs b w -> b -> Eff effs w Source #

Function application in the context of an array of effects, Arrs effs b w.

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

Composition of effectful arrows (Arrs). Allows for the caller to change the effect environment, as well.

Nondeterminism Effect

data NonDet a where Source #

A data type for representing nondeterminstic choice.

Constructors

MZero :: NonDet a 
MPlus :: NonDet Bool