Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Sem r a = Sem {}
- type Member e r = Member' e r
- type family Members es r :: Constraint where ...
- send :: Member e r => e (Sem r) a -> Sem r a
- sendM :: Member (Lift m) r => m a -> Sem r a
- run :: Sem '[] a -> a
- runM :: Monad m => Sem '[Lift m] a -> m a
- raise :: forall e r a. Sem r a -> Sem (e ': r) a
- newtype Lift m (z :: * -> *) a where
- usingSem :: Monad m => (forall x. Union r (Sem r) x -> m x) -> Sem r a -> m a
- liftSem :: Union r (Sem r) a -> Sem r a
- hoistSem :: (forall x. Union r (Sem r) x -> Union r' (Sem r') x) -> Sem r a -> Sem r' a
- (.@) :: Monad m => (forall x. Sem r x -> m x) -> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r y) -> Sem (e ': r) z -> m z
- (.@@) :: Monad m => (forall x. Sem r x -> m x) -> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r (f y)) -> Sem (e ': r) z -> m (f z)
Documentation
The Sem
monad handles computations of arbitrary extensible effects.
A value of type Sem r
describes a program with the capabilities of
r
. For best results, r
should always be kept polymorphic, but you can
add capabilities via the Member
constraint.
The value of the Sem
monad is that it allows you to write programs
against a set of effects without a predefined meaning, and provide that
meaning later. For example, unlike with mtl, you can decide to interpret an
Error
effect tradtionally as an Either
, or instead
significantly faster as an IO
Exception
. These
interpretations (and others that you might add) may be used interchangably
without needing to write any newtypes or Monad
instances. The only
change needed to swap interpretations is to change a call from
runError
to runErrorInIO
.
The effect stack r
can contain arbitrary other monads inside of it. These
monads are lifted into effects via the Lift
effect. Monadic values can be
lifted into a Sem
via sendM
.
A Sem
can be interpreted as a pure value (via run
) or as any
traditional Monad
(via runM
). Each effect E
comes equipped with some
interpreters of the form:
runE ::Sem
(E ': r) a ->Sem
r a
which is responsible for removing the effect E
from the effect stack. It
is the order in which you call the interpreters that determines the
monomorphic representation of the r
parameter.
After all of your effects are handled, you'll be left with either
a
or a Sem
'[] a
value, which can be
consumed respectively by Sem
'[ Lift
m ] arun
and runM
.
Examples
As an example of keeping r
polymorphic, we can consider the type
Member
(State
String) r =>Sem
r ()
to be a program with access to
get
::Sem
r Stringput
:: String ->Sem
r ()
methods.
By also adding a
Member
(Error
Bool) r
constraint on r
, we gain access to the
throw
:: Bool ->Sem
r acatch
::Sem
r a -> (Bool ->Sem
r a) ->Sem
r a
functions as well.
In this sense, a
constraint is
analogous to mtl's Member
(State
s) r
and should
be thought of as such. However, unlike mtl, a MonadState
s mSem
monad may have
an arbitrary number of the same effect.
For example, we can write a Sem
program which can output either
Int
s or Bool
s:
foo :: (Member
(Output
Int) r ,Member
(Output
Bool) r ) =>Sem
r () foo = dooutput
@Int 5output
True
Notice that we must use -XTypeApplications
to specify that we'd like to
use the (Output
Int
) effect.
Since: 0.1.2.0
Instances
Monad (Sem f) Source # | |
Functor (Sem f) Source # | |
Member Fixpoint r => MonadFix (Sem r) Source # | |
Defined in Polysemy.Internal | |
Applicative (Sem f) Source # | |
Member (Lift IO) r => MonadIO (Sem r) Source # | This instance will only lift |
Defined in Polysemy.Internal | |
Member NonDet r => Alternative (Sem r) Source # | |
type Member e r = Member' e r Source #
A proof that the effect e
is available somewhere inside of the effect
stack r
.
type family Members es r :: Constraint where ... Source #
Makes constraints of functions that use multiple effects shorter by
translating single list of effects into multiple Member
constraints:
foo ::Members
'[Output
Int ,Output
Bool ,State
String ] r =>Sem
r ()
translates into:
foo :: (Member
(Output
Int) r ,Member
(Output
Bool) r ,Member
(State
String) r ) =>Sem
r ()
Since: 0.1.2.0
newtype Lift m (z :: * -> *) a where Source #
An effect which allows a regular Monad
m
into the Sem
ecosystem. Monadic actions in m
can be lifted into Sem
via
sendM
.
For example, you can use this effect to lift IO
actions directly into
Sem
:
sendM
(putStrLn "hello") ::Member
(Lift
IO) r =>Sem
r ()
That being said, you lose out on a significant amount of the benefits of
Sem
by using sendM
directly in application code; doing
so will tie your application code directly to the underlying monad, and
prevent you from interpreting it differently. For best results, only use
Lift
in your effect interpreters.
Consider using trace
and runTraceIO
as
a substitute for using putStrLn
directly.
usingSem :: Monad m => (forall x. Union r (Sem r) x -> m x) -> Sem r a -> m a Source #
Like runSem
but flipped for better ergonomics sometimes.
:: Monad m | |
=> (forall x. Sem r x -> m x) | The lowering function, likely |
-> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r y) | |
-> Sem (e ': r) z | |
-> m z |
Some interpreters need to be able to lower down to the base monad (often
IO
) in order to function properly --- some good examples of this are
runErrorInIO
and runResource
.
However, these interpreters don't compose particularly nicely; for example,
to run runResource
, you must write:
runM . runErrorInIO runM
Notice that runM
is duplicated in two places here. The situation gets
exponentially worse the more intepreters you have that need to run in this
pattern.
Instead, .@
performs the composition we'd like. The above can be written as
(runM .@ runErrorInIO)
The parentheses here are important; without them you'll run into operator precedence errors.