Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Writer w m k
- tell :: (Member (Writer w) sig, Carrier sig m) => w -> m ()
- listen :: (Member (Writer w) sig, Carrier sig m) => m a -> m (w, a)
- listens :: (Member (Writer w) sig, Carrier sig m) => (w -> b) -> m a -> m (b, a)
- censor :: (Member (Writer w) sig, Carrier sig m) => (w -> w) -> m a -> m a
- runWriter :: Monoid w => WriterC w m a -> m (w, a)
- execWriter :: (Monoid w, Functor m) => WriterC w m a -> m w
- newtype WriterC w m a = WriterC {
- runWriterC :: StateC w m a
Documentation
tell :: (Member (Writer w) sig, Carrier sig m) => w -> m () Source #
Write a value to the log.
fst (run (runWriter (mapM_ (tell . Sum) (0 : ws)))) == foldMap Sum ws
listen :: (Member (Writer w) sig, Carrier sig m) => m a -> m (w, a) Source #
Run a computation, returning the pair of its output and its result.
run (runWriter (fst <$ tell (Sum a) <*> listen @(Sum Integer) (tell (Sum b)))) == (Sum a <> Sum b, Sum b)
listens :: (Member (Writer w) sig, Carrier sig m) => (w -> b) -> m a -> m (b, a) Source #
Run a computation, applying a function to its output and returning the pair of the modified output and its result.
run (runWriter (fst <$ tell (Sum a) <*> listens @(Sum Integer) (applyFun f) (tell (Sum b)))) == (Sum a <> Sum b, applyFun f (Sum b))
censor :: (Member (Writer w) sig, Carrier sig m) => (w -> w) -> m a -> m a Source #
Run a computation, modifying its output with the passed function.
run (execWriter (censor (applyFun f) (tell (Sum a)))) == applyFun f (Sum a)
run (execWriter (tell (Sum a) *> censor (applyFun f) (tell (Sum b)) *> tell (Sum c))) == (Sum a <> applyFun f (Sum b) <> Sum c)
newtype WriterC w m a Source #
A space-efficient carrier for Writer
effects.
This is based on a post Gabriel Gonzalez made to the Haskell mailing list: https://mail.haskell.org/pipermail/libraries/2013-March/019528.html
WriterC | |
|
Instances
MonadTrans (WriterC w) Source # | |
Defined in Control.Effect.Writer | |
Monad m => Monad (WriterC w m) Source # | |
Functor m => Functor (WriterC w m) Source # | |
MonadFail m => MonadFail (WriterC w m) Source # | |
Defined in Control.Effect.Writer | |
Monad m => Applicative (WriterC w m) Source # | |
Defined in Control.Effect.Writer | |
MonadIO m => MonadIO (WriterC w m) Source # | |
Defined in Control.Effect.Writer | |
(Alternative m, Monad m) => Alternative (WriterC w m) Source # | |
(Alternative m, Monad m) => MonadPlus (WriterC w m) Source # | |
(Monoid w, Carrier sig m, Effect sig) => Carrier (Writer w :+: sig) (WriterC w m) Source # | |