Copyright | (c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o. |
---|---|
License | BSD3 |
Maintainer | ixcom-core@ixperta.com |
Stability | experimental |
Portability | GHC specific language extensions. |
Safe Haskell | None |
Language | Haskell2010 |
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.
- data Eff effs a
- type Arr effs a b = a -> Eff effs b
- type Arrs effs a b = FTCQueue (Eff effs) a b
- module Data.OpenUnion
- module Data.FTCQueue
- send :: Member eff effs => eff a -> Eff effs a
- run :: Eff '[] a -> a
- runM :: Monad m => Eff '[m] a -> m a
- handleRelay :: (a -> Eff effs b) -> (forall v. eff v -> Arr effs v b -> Eff effs b) -> Eff (eff ': effs) a -> Eff effs b
- handleRelayS :: s -> (s -> a -> Eff effs b) -> (forall v. s -> eff v -> (s -> Arr effs v b) -> Eff effs b) -> Eff (eff ': effs) a -> Eff effs b
- 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
- qApp :: Arrs effs b w -> b -> Eff effs w
- qComp :: Arrs effs a b -> (Eff effs b -> Eff effs' c) -> Arr effs' a c
- data NonDet a where
Effect Monad
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.
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.
module Data.OpenUnion
Fast Type-aligned Queue
Fast type-aligned queue optimized to effectful functions of type
(a -> m b)
.
module Data.FTCQueue
Sending Arbitrary Effect
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
:: (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 ': effs) a | |
-> Eff effs b | Result with effects of type |
Given a request, either handle it or relay it.
:: 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 ': effs) a | |
-> Eff effs b | Result with effects of type |
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.