Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Monad m => Carrier m where
- type EffPrimHandler e m = forall x. e m x -> m x
- interpretPrimSimple :: forall e m a p. (RepresentationalEff e, Threaders '[ReaderThreads] m p, ReaderThreads '[e], Carrier m) => EffPrimHandler e m -> InterpretPrimSimpleC e m a -> m a
- interpretPrimViaHandler :: forall h e m a. PrimHandler h e m => InterpretPrimC h e m a -> m a
- class (RepresentationalEff e, Carrier m) => PrimHandler (h :: Type) e m where
- effPrimHandler :: EffPrimHandler e m
- interpretPrim :: forall e m a. (RepresentationalEff e, Carrier m) => EffPrimHandler e m -> InterpretPrimReifiedC e m a -> m a
- class Threads t p where
- class RepresentationalEff e => ThreadsEff t e where
- data InterpretPrimSimpleC (e :: Effect) (m :: Type -> Type) a
- data InterpretPrimC (s :: Type) (e :: Effect) (m :: Type -> Type) a
- type InterpretPrimReifiedC e m a = forall s. ReifiesPrimHandler s e m => InterpretPrimC (ViaReifiedH s) e m a
Primitive effects
class Monad m => Carrier m Source #
The class of effect carriers, and the underlying mechanism with which effects are implemented.
Each carrier is able to implement a number of derived effects, and primitive effects. Users usually only interact with derived effects, as these determine the effects that users have access to.
The standard interpretation tools are typically powerful enough to
let you avoid making instances of this class directly. If you need to make
your own instance of Carrier
, import Control.Effect.Carrier and consult the
wiki.
type Derivs m :: [Effect] Source #
The derived effects that m
carries. Each derived effect is eventually
reformulated into terms of the primitive effects
or other
effects in Prims
m
.Derivs
m
In application code, you gain access to effects by placing membership
constraints upon
. You can use Derivs
mEff
or Effs
for this
purpose.
Although rarely relevant for users,
can also contain effects
that aren't expressed in terms of other effects, as longs as the handlers
for those effects can be lifted generically using Derivs
mlift
. Such effects don't
need to be part of
, which is exclusively for primitive effects
whose handlers need special treatment to be lifted.Prims
m
For example, first order effects such as State
never need to be part of
. Certain higher-order effects -
such as Prims
mCont
- can also be handled such that they
never need to be primitive.
type Prims m :: [Effect] Source #
The primitive effects that m
carries. These are higher-order effects
whose handlers aren't expressed in terms of other effects, and thus need to
be lifted on a carrier-by-carrier basis.
Never place membership constraints on
.
You should only gain access to effects by placing membership constraints
on Prims
m
.Derivs
m
However, running interpreters may place other kinds of constraints upon
, namely threading constraints, marked by the use of
Prims
mThreaders
.
If you want to run such an effect interpreter inside application code, you
have to propagate such threading constraints through your application.
should only contain higher-order effects that can't be lifted
generically using Prims
mlift
. Any other effects can be placed in
.Derivs
m
Instances
Interpretation of primitive effects
type EffPrimHandler e m = forall x. e m x -> m x Source #
The type of effect handlers for a primitive effect e
with current
carrier m
.
Unlike EffHandler
s, EffPrimHandler
s have direct access to m
,
making them significantly more powerful.
That said, you should interpret your own effects as primitives only as a
last resort. Every primitive effect comes at the cost of enormous amounts
of boilerplate: namely, the need for a ThreadsEff
instance for every
monad transformer that can thread that effect.
Some effects in this library are intended to be used as primitive effects,
such as Regional
. Try to use such effects
to gain the power you need to interpret your effects instead of
defining your own primitive effects, since the primitive effects offered
in this library already have ThreadsEff
instances defined for them.
interpretPrimSimple
interpretPrimSimple :: forall e m a p. (RepresentationalEff e, Threaders '[ReaderThreads] m p, ReaderThreads '[e], Carrier m) => EffPrimHandler e m -> InterpretPrimSimpleC e m a -> m a Source #
A significantly slower variant of interpretPrim
that doesn't have
a higher-ranked type, making it much easier to use partially applied.
Only interpret your own effects as primitives as a last resort.
See EffPrimHandler
.
Derivs
(InterpretPrimSimpleC
e m) = e ':Derivs
m
Prims
(InterpretPrimSimpleC
e m) = e ':Prims
m
Note the ReaderThreads '[e]
constraint, meaning
you need to define a ThreadsEff e (ReaderT i)
instance in order
to use interpretPrimSimple
.
interpretPrimViaHandler
interpretPrimViaHandler :: forall h e m a. PrimHandler h e m => InterpretPrimC h e m a -> m a Source #
Interpret an effect as a new primitive effect by using
an explicit PrimHandler
instance.
See PrimHandler
for more information.
Only interpret your own effects as primitives as a last resort.
See EffPrimHandler
.
class (RepresentationalEff e, Carrier m) => PrimHandler (h :: Type) e m where Source #
The class of effect handlers for primitive effects.
Instances of this class can be used together interpretPrimViaHandler
in order to interpret primitive effects.
h
is the tag for the handler, e
is the effect to interpret,
and m
is the Carrier
on which the handler operates.
To define your own interpreter using this method, create a new
datatype without any constructors to serve as the tag
for the handler, and then define a PrimHandler
instance for it.
Then, you can use your handler to interpret effects with
interpretPrimViaHandler
.
Alternatively, you can use interpretPrim
or interpretPrimSimple
,
which lets you avoid the need to define instances of PrimHandler
,
but come at other costs.
Only interpret your own effects as primitives as a last resort.
See EffPrimHandler
.
effPrimHandler :: EffPrimHandler e m Source #
Instances
interpretPrim
interpretPrim :: forall e m a. (RepresentationalEff e, Carrier m) => EffPrimHandler e m -> InterpretPrimReifiedC e m a -> m a Source #
Interpret an effect as a new primitive effect.
Only interpret your own effects as primitives as a last resort.
See EffPrimHandler
.
Derivs
(InterpretPrimReifiedC
e m) = e ':Derivs
m
Prims
(InterpretPrimReifiedC
e m) = e ':Prims
m
This has a higher-rank type, as it makes use of InterpretPrimReifiedC
.
This makes interpretPrim
very difficult to use partially applied.
In particular, it can't be composed using
. You must use
paranthesis or .
$
.
Consider using interpretPrimSimple
instead if performance is secondary.
Threading primitive effects
class Threads t p where Source #
is satisfied if Threads
t p
instances are defined for
each effect ThreadsEff
t ee
in p
. By using the
constraint, you're
able to lift Threads
t pAlgebra
s over p
from any monad m
to t m
. This is useful
when defining custom Carrier
instances.
Note that you should not place a
constraint if Threads
t pt
is
simply a newtype over an existsing monad transformer u
that already has
ThreadsEff
instances defined for it. Instead, you should place a
constraint, and use its Threads
u pthread
by coercing the resulting
algebra from
to Algebra
p (u m)
'.
That way, you avoid having to define redundant Algebra
p (t m)ThreadsEff
instances for
every newtype of a monad transformer.
Threads
forms the basis of threading constraints
(see Threaders
), and every threading constraint offered
in the library makes use of Threads
in one way or another.
class RepresentationalEff e => ThreadsEff t e where Source #
An instance of ThreadsEff
represents the ability for a monad transformer
t
to thread a primitive effect e
-- i.e. lift handlers of that effect.
Instances of ThreadsEff
are accumulated into entire stacks of primitive
effects by Threads
.
You only need to make ThreadsEff
instances for monad transformers that
aren't simply newtypes over existing monad transformers. You also don't need
to make them for IdentityT
.
Instances
Carriers
data InterpretPrimSimpleC (e :: Effect) (m :: Type -> Type) a Source #
Instances
data InterpretPrimC (s :: Type) (e :: Effect) (m :: Type -> Type) a Source #
Instances
type InterpretPrimReifiedC e m a = forall s. ReifiesPrimHandler s e m => InterpretPrimC (ViaReifiedH s) e m a Source #