Copyright | (c) Michael Szvetits 2020 |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | typedbyte@qualified.name |
Stability | stable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
The writer effect, similar to the MonadWriter
type class from the mtl
library.
Lazy and strict interpretations of the effect are available here: Control.Effect.Writer.Lazy and Control.Effect.Writer.Strict.
Synopsis
- class (Monad m, Monoid w) => Writer' tag w m | tag m -> w where
- listens' :: forall tag w b m a. Writer' tag w m => (w -> b) -> m a -> m (b, a)
- type Writer w = Writer' G w
- tell :: Writer w m => w -> m ()
- listen :: Writer w m => m a -> m (w, a)
- censor :: Writer w m => (w -> w) -> m a -> m a
- listens :: Writer w m => (w -> b) -> m a -> m (b, a)
- tagWriter' :: forall new w m a. (Writer' G w `Via` Tagger G new) m a -> m a
- retagWriter' :: forall tag new w m a. (Writer' tag w `Via` Tagger tag new) m a -> m a
- untagWriter' :: forall tag w m a. (Writer' tag w `Via` Tagger tag G) m a -> m a
Tagged Writer Effect
class (Monad m, Monoid w) => Writer' tag w m | tag m -> w where Source #
An effect that adds a write-only, accumulated output to a given computation.
Produces the output w
. In other words, w
is appended to the accumulated output.
listen' :: m a -> m (w, a) Source #
Executes a sub-computation and appends w
to the accumulated output.
:: (w -> w) | The function which is applied to the output. |
-> m a | The sub-computation which produces the modified output. |
-> m a | The result of the sub-computation. |
Executes a sub-computation and applies the function to its output.
Instances
(Monad m, Monoid w) => Writer' (tag :: k) w (WriterT w m) Source # | |
(Monad m, Monoid w) => Writer' (tag :: k) w (WriterT w m) Source # | |
Writer' tag w m => Writer' (tag :: k) w (Separation m) Source # | |
Defined in Control.Effect.RWS tell' :: w -> Separation m () Source # listen' :: Separation m a -> Separation m (w, a) Source # censor' :: (w -> w) -> Separation m a -> Separation m a Source # | |
(Monoid w, Monad m) => Writer' (tag :: k) w (WriterT w m) Source # | |
Handle '[Monad] (Writer' tag w) others t m => Writer' (tag :: k) w (EachVia (Writer' tag w ': others) t m) Source # | |
Defined in Control.Effect.Writer | |
Find '[Monad] (Writer' tag w) other effs t m => Writer' (tag :: k) w (EachVia (other ': effs) t m) Source # | |
Control '[Monad] (Writer' tag w) t m => Writer' (tag :: k) w (EachVia ('[] :: [Effect]) t m) Source # | |
(Monad m, Monoid w) => Writer' (tag :: k) w (RWST r w s m) Source # | |
(Monad m, Monoid w) => Writer' (tag :: k) w (RWST r w s m) Source # | |
(Monad m, Monoid w) => Writer' (tag :: k) w (RWST r w s m) Source # | |
Writer' new w m => Writer' (tag :: k2) w (Tagger tag new m) Source # | |
Convenience Functions
:: forall tag w b m a. Writer' tag w m | |
=> (w -> b) | The function which is applied to the output. |
-> m a | The sub-computation which produces the modified output. |
-> m (b, a) | The result of the sub-computation, including the modified output. |
Executes a sub-computation and applies the function to its output, thus adding an additional value to the result of the sub-computation.
Untagged Writer Effect
If you don't require disambiguation of multiple writer effects (i.e., you only have one writer effect in your monadic context), it is recommended to always use the untagged writer effect.
Tagging and Untagging
Conversion functions between the tagged and untagged writer effect, usually used in combination with type applications, like:
tagWriter'
@"newTag" programretagWriter'
@"oldTag" @"newTag" programuntagWriter'
@"erasedTag" program