Safe Haskell | None |
---|---|
Language | Haskell2010 |
eff
is a fast, flexible, easy to use effect system for Haskell. eff
makes it easy to write composable, modular effects and effect handlers without
sacrificing performance. Broadly speaking, eff
provides the following
features:
- The
Eff
monad, which provides an extremely flexible set of control operations that can be used to implement a variety of effects. - A standard library of built-in effects and effect handlers, including common
effects like
Reader
,State
, andError
. - A framework for defining your own effects and effect handlers, which can
either be built from scratch using the
Eff
primitives or by delegating to an existing handler.
eff
is far from the first effect system for Haskell, but it differentiates
itself from existing libraries in the following respects:
eff
is built atop a direct, low-level implementation of delimited continuations to provide the best performance possible.eff
provides a simpler, more streamlined API for handling effects.- Like
polysemy
andfused-effects
(but unlikefreer-simple
),eff
supports so called “scoped” effect operations likelocal
andcatch
, but unlikepolysemy
andfused-effects
(and also unliketransformers
/mtl
),eff
provides a consistent semantics for such operations regardless of handler order.
eff
aspires to be a turnkey replacement for most traditional uses of monad
transformers. eff
provides comparable performance to transformers
and mtl
with less complexity, less boilerplate, and a simpler semantics.
Synopsis
- data Eff effs a
- run :: Eff '[] a -> a
- lift :: forall effs1 effs2 a. Lift effs1 effs2 => Eff effs1 a -> Eff effs2 a
- lift1 :: forall eff effs a. Eff effs a -> Eff (eff ': effs) a
- type Effect = (Type -> Type) -> Type -> Type
- send :: forall eff a effs. eff :< effs => eff (Eff effs) a -> Eff effs a
- class eff :< effs
- class effs1 :<< effs2
- interpret :: forall eff a effs. (forall m b. eff m b -> Eff (eff ': effs) b) -> Eff (eff ': effs) a -> Eff effs a
- data Handle eff effs i r effs' a
- handle :: forall eff a r effs. (a -> Eff effs r) -> (forall effs' b. eff :< effs' => eff (Eff effs') b -> Handle eff effs a r effs' b) -> Eff (eff ': effs) a -> Eff effs r
- liftH :: Eff (eff ': effs) a -> Handle eff effs i r effs' a
- abort :: r -> Handle eff effs i r effs' a
- control :: ((a -> Eff effs r) -> Eff effs r) -> Handle eff effs i r effs' a
- control0 :: ((a -> Eff (eff ': effs) i) -> Eff effs r) -> Handle eff effs i r effs' a
- locally :: Eff effs' a -> Handle eff effs i r effs' a
- data IOE :: Effect where
- class Monad m => MonadIO (m :: Type -> Type) where
- runIO :: Eff '[IOE] a -> IO a
- (&) :: a -> (a -> b) -> b
- (>>>) :: forall k cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c
- module Control.Effect.Coroutine
- module Control.Effect.Error
- module Control.Effect.NonDet
- module Control.Effect.Reader
- module Control.Effect.State.Strict
- module Control.Effect.Writer.Strict
The Eff
monad
All eff
computations operate in the Eff
monad. Eff
computations are
parameterized by a type-level list that specifies which effects they are
allowed to perform. For example, a computation of type
can raise exceptions of type Eff
'[Error
e, Reader
r, State
s] ae
, can access a global environment of type
r
, and can read and modify a single cell of mutable state of type s
.
To run an Eff
computation that performs effects, the effects must be
explicitly handled. Functions that handle effects are called
effect handlers, and they usually have types like the following:
runX ::Eff
(X ': effs) a ->Eff
effs a
Note that the argument to runX
can perform the X
effect, but the result
cannot! Any X
operations have been handled by runX
, which interprets
their meaning. Examples of effect handlers include
runError
, runReader
, and
runState
.
After all effects have been handled, the resulting computation will have type
, a computation that performs no effects. A computation with
this type is pure, so it can be converted to an ordinary value using Eff
'[] arun
.
Some effects cannot be handled locally, but instead require performing I/O.
These effects will delegate to the IOE
effect, which provides low-level
interop with Haskell’s built-in IO
monad. After all other effects have been
handled, a computation of type
can be converted to an
ordinary Eff
'[IOE
] a
computation using IO
arunIO
.
lift :: forall effs1 effs2 a. Lift effs1 effs2 => Eff effs1 a -> Eff effs2 a Source #
Lifts an Eff
computation into one that performs all the same effects, and
possibly more. For example, if you have a computation
m :: Eff
'[Foo, Bar] ()
then lift
will transform it into a polymorphic computation with the
following type:
lift
m :: (Foo:<
effs, Bar:<
effs) =>Eff
effs ()
This type is much more general, and effs
can now be instantiated at many
different types. Generally, lift
can manipulate the list of effects in any
of the following ways:
- Effects can be reordered.
- New effects can be inserted anywhere in the list.
- Duplicate effects can be collapsed.
More generally, the list of effects doesn’t need to be entirely concrete in
order for lift
to work. For example, if you have a computation
n :: Eff
(Foo ': Bar ': effs1) ()
then
will have the following type:lift
n
lift
n :: (Foo:<
effs2, Bar:<
effs2, effs1:<<
effs2) =>Eff
effs2 ()
This type is extremely general, and it allows lift
to manipulate the head
of the effects list even if the entire list is not completely known.
The Lift
typeclass provides some type-level programming machinery to
implement lift
, but it should be treated as an implementation detail. In
most situations, the machinery should “just work,” but if it doesn’t, the
type errors can be somewhat inscrutable. In those situations, adding some
explicit type annotations (or using TypeApplications
) can improve the type
errors significantly.
Defining new effects
Instances
eff :< effs => eff :< (eff' ': effs) Source # | |
Defined in Control.Effect.Internal reifyIndex :: Int Source # | |
eff :< (eff ': effs) Source # | |
Defined in Control.Effect.Internal reifyIndex :: Int Source # | |
type DictRep (eff :< effs) Source # | |
Defined in Control.Effect.Internal |
class effs1 :<< effs2 Source #
Instances
(effs2 ~ (eff ': effs3), effs1 :<< effs3) => effs1 :<< effs2 Source # | |
Defined in Control.Effect.Internal reifySubIndex :: Int Source # | |
effs :<< effs Source # | |
Defined in Control.Effect.Internal reifySubIndex :: Int Source # | |
type DictRep (effs1 :<< effs2) Source # | |
Defined in Control.Effect.Internal |
Handling effects
Simple effect handlers
:: (forall m b. eff m b -> Eff (eff ': effs) b) | The handler function. |
-> Eff (eff ': effs) a | The action to handle. |
-> Eff effs a |
The simplest way to handle an effect. Each use of send
for the handled
effect dispatches to the handler function, which provides an interpretation
for the operation. The handler function may handle the operation directly, or
it may defer to other effects currently in scope.
Most effect handlers should be implemented using interpret
, possibly with
the help of additional Error
or State
effects.
Especially complex handlers can be defined via the more general handle
,
which interpret
is defined in terms of:
interpret
f =handle
(liftH
.
f)
Advanced effect handlers
data Handle eff effs i r effs' a Source #
The monad that effect handlers run in.
- The
eff
parameter is the effect being handled, and theeffs
parameter includes the other effects in scope at the point of thehandle
call (used byliftH
). - The
i
parameter is the return type of the handled computation before the exit handler has been applied (used bycontrol0
). - The
r
parameter is the final return type of the handled computation (used byabort
,control
, andcontrol0
). - The
effs'
parameter is the list of effects in scope at the point of the originatingsend
call (used bylocally
).
See handle
for more details.
Instances
Monad (Handle eff effs i r effs') Source # | |
Functor (Handle eff effs i r effs') Source # | |
Applicative (Handle eff effs i r effs') Source # | |
Defined in Control.Effect.Internal pure :: a -> Handle eff effs i r effs' a # (<*>) :: Handle eff effs i r effs' (a -> b) -> Handle eff effs i r effs' a -> Handle eff effs i r effs' b # liftA2 :: (a -> b -> c) -> Handle eff effs i r effs' a -> Handle eff effs i r effs' b -> Handle eff effs i r effs' c # (*>) :: Handle eff effs i r effs' a -> Handle eff effs i r effs' b -> Handle eff effs i r effs' b # (<*) :: Handle eff effs i r effs' a -> Handle eff effs i r effs' b -> Handle eff effs i r effs' a # |
:: (a -> Eff effs r) | The exit handler, aka the action to take on normal returns (often just |
-> (forall effs' b. eff :< effs' => eff (Eff effs') b -> Handle eff effs a r effs' b) | The handler function. |
-> Eff (eff ': effs) a | The action to handle. |
-> Eff effs r |
Handles the topmost effect in an Eff
computation. The given handler
function must provide an interpretation for each effectful operation. The
handler runs in the restrictive Handle
monad, which generally uses one of
the following core Handle
operations:
liftH
— Runs an action in the context of the originalhandle
call. This is the most common way to handle an effect.abort
— Aborts the computation to thehandle
call and returns a value directly. This is usually used to implement exception-like operations.control
— Captures the current continuation up to and including thehandle
call and aborts, passing the captured continuation to the handler. This can be used to implement complex control operators such as coroutines or resumable exceptions.control0
— Likecontrol
, but does not include thehandle
call itself in the captured continuation, so a different handler may be installed before resuming the computation.locally
— Runs an action directly in the context of the originatingsend
call. This can be used to implement “scoped” operations likelocal
andcatch
.
See the documentation for each of the above functions for examples and more details.
Performing I/O
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
Re-exports
(>>>) :: forall k cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c infixr 1 #
Left-to-right composition
Built-in effects
module Control.Effect.Coroutine
module Control.Effect.Error
module Control.Effect.NonDet
module Control.Effect.Reader
module Control.Effect.State.Strict
module Control.Effect.Writer.Strict