Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data WriterPrim o :: Effect where
- WriterPrimTell :: o -> WriterPrim o m ()
- WriterPrimListen :: m a -> WriterPrim o m (o, a)
- WriterPrimPass :: m (o -> o, a) -> WriterPrim o m a
- threadWriterPrim :: forall o t m a. (MonadTrans t, ThreadsEff t (ListenPrim o), Monad m) => ((forall x. WriterPrim o m x -> m x) -> t m (o -> o, a) -> t m a) -> (forall x. WriterPrim o m x -> m x) -> WriterPrim o (t m) a -> t m a
- threadWriterPrimViaClass :: forall o t m a. (Monoid o, MonadTrans t, Monad m) => (RepresentationalT t, forall b. MonadWriter o b => MonadWriter o (t b)) => (forall x. WriterPrim o m x -> m x) -> WriterPrim o (t m) a -> t m a
- algListenPrimIntoWriterPrim :: Algebra' (ListenPrim o ': p) m a -> (m (o -> o, a) -> m a) -> Algebra' (WriterPrim o ': p) m a
Effects
data WriterPrim o :: Effect where Source #
A primitive effect that may be used for
interpreters of connected Tell
,
Listen
, and Pass
effects.
This combines Tell
and
Listen
and Pass
.
This may be relevant if there are monad transformers that may only lift
pass
if they also have access to
listen
and tell
.
WriterPrim
is only used as a primitive effect.
If you define a Carrier
that relies on a novel
non-trivial monad transformer t
, then you need to make
a
instance (if possible).
Monoid
o => ThreadsEff
t (WriterPrim
o)threadWriterPrim
and threadWriterPrimViaClass
can help you with that.
The following threading constraints accept WriterPrim
:
WriterPrimTell :: o -> WriterPrim o m () | |
WriterPrimListen :: m a -> WriterPrim o m (o, a) | |
WriterPrimPass :: m (o -> o, a) -> WriterPrim o m a |
Instances
Threading utilities
threadWriterPrim :: forall o t m a. (MonadTrans t, ThreadsEff t (ListenPrim o), Monad m) => ((forall x. WriterPrim o m x -> m x) -> t m (o -> o, a) -> t m a) -> (forall x. WriterPrim o m x -> m x) -> WriterPrim o (t m) a -> t m a Source #
Construct a valid definition of threadEff
for a
instance only be specifying how
ThreadsEff
t (WriterPrim
o)WriterPrimPass
should be lifted.
This relies on an existing
instance.ThreadsEff
t (ListenPrim
o)
threadWriterPrimViaClass :: forall o t m a. (Monoid o, MonadTrans t, Monad m) => (RepresentationalT t, forall b. MonadWriter o b => MonadWriter o (t b)) => (forall x. WriterPrim o m x -> m x) -> WriterPrim o (t m) a -> t m a Source #
A valid definition of threadEff
for a
instance,
given that Monoid
o => ThreadsEff
(WriterPrim
o) tt
lifts
.MonadWriter
w
Combinators for Algebra
s
algListenPrimIntoWriterPrim :: Algebra' (ListenPrim o ': p) m a -> (m (o -> o, a) -> m a) -> Algebra' (WriterPrim o ': p) m a Source #
Rewrite an Algebra
where the topmost effect is ListenPrim
into
an Algebra
where the topmost effect is WriterPrim
by providing
an implementation of WriterPrimPass
.