freer-0.2.4.1: Implementation of the Freer Monad

CopyrightAllele Dev 2016
LicenseBSD-3
Maintainerallele.dev@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Freer.Internal

Description

Internal machinery for this effects library. This includes:

  • Eff data type, for expressing effects
  • NonDetEff 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

Documentation

data Eff r a Source #

The Eff representation.

Status of a coroutine (client): * Val: Done with the value of type a * E : Sending a request of type Union r with the continuation Arrs r b a

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 # 

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 #

Member NonDetEff r => Alternative (Eff r) Source # 

Methods

empty :: Eff r a #

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

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

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

Member NonDetEff r => MonadPlus (Eff r) Source # 

Methods

mzero :: Eff r a #

mplus :: Eff r a -> Eff r a -> Eff r a #

class Member' t r (FindElem t r) => Member t r where Source #

Minimal complete definition

inj, prj

Methods

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

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

Instances

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

Methods

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

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

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

Equations

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

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

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

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

data Union r v Source #

Instances

(Functor f1, Functor (Union ((:) (* -> *) f2 fs))) => Functor (Union ((:) (* -> *) f1 ((:) (* -> *) f2 fs))) Source # 

Methods

fmap :: (a -> b) -> Union (((* -> *) ': f1) (((* -> *) ': f2) fs)) a -> Union (((* -> *) ': f1) (((* -> *) ': f2) fs)) b #

(<$) :: a -> Union (((* -> *) ': f1) (((* -> *) ': f2) fs)) b -> Union (((* -> *) ': f1) (((* -> *) ': f2) fs)) a #

Functor f => Functor (Union ((:) (* -> *) f ([] (* -> *)))) Source # 

Methods

fmap :: (a -> b) -> Union (((* -> *) ': f) [* -> *]) a -> Union (((* -> *) ': f) [* -> *]) b #

(<$) :: a -> Union (((* -> *) ': f) [* -> *]) b -> Union (((* -> *) ': f) [* -> *]) a #

data NonDetEff a where Source #

A data type for representing nondeterminstic choice

Constructors

MZero :: NonDetEff a 
MPlus :: NonDetEff Bool 

makeChoiceA :: Alternative f => Eff (NonDetEff ': r) a -> Eff r (f a) Source #

A handler for nondeterminstic effects

msplit :: Member NonDetEff r => Eff r a -> Eff r (Maybe (a, Eff r a)) Source #

decomp :: Union (t ': r) v -> Either (Union r v) (t v) Source #

tsingleton :: (a -> m b) -> FTCQueue m a b Source #

Build a leaf from a single operation [O(1)]

extract :: Union '[t] v -> t v Source #

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

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

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

Composition of effectful arrows Allows for the caller to change the effect environment, as well

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

send a request and wait for a reply

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

Runs a set of Effects. Requires that all effects are consumed. Typically composed as follows: > run . runEff1 eff1Arg . runEff2 eff2Arg1 eff2Arg2 (program)

runM :: Monad m => Eff '[m] w -> m w 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.

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

Given a request, either handle it or relay it.

handleRelayS :: 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 handleRelay Allows sending along some state to be handled for the target effect, or relayed to a handler that can handle the target effect.

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