Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module duplicates the Control.Monad.Writer module from the mtl, for constrained monads. It also provides a non-leaky writer monad.
- class (Monoid w, Monad m) => MonadWriter w m | m -> w where
- type WriterSuitable m a :: Constraint
- data WriterT s m a
- pattern WriterT :: forall m s a. (Functor m, Monoid s, Suitable m (a, s)) => m (a, s) -> WriterT s m a
- type Writer s = WriterT s Identity
- runWriterT :: Monoid s => WriterT s m a -> m (a, s)
- execWriterT :: (Monad m, Monoid s, Suitable m s) => WriterT s m a -> m s
- execWriter :: Monoid s => Writer s a -> s
- runWriter :: Monoid s => Writer s a -> (a, s)
- listen :: (MonadWriter w m, WriterSuitable m (a, w)) => m a -> m (a, w)
- pass :: (MonadWriter w m, Suitable m a, WriterSuitable m (a, w -> w)) => m (a, w -> w) -> m a
- evalWriterT :: (Monad m, Monoid s, Suitable m a) => WriterT s m a -> m a
- evalWriter :: Monoid s => Writer s a -> a
Documentation
class (Monoid w, Monad m) => MonadWriter w m | m -> w where Source #
A class for monads with logging ability.
type WriterSuitable m a :: Constraint Source #
writer :: WriterSuitable m a => (a, w) -> m a Source #
Embed a simple writer action.
tell :: WriterSuitable m () => w -> m () Source #
Log some output.
listenC :: WriterSuitable m b => (a -> w -> b) -> m a -> m b Source #
This is equivalent to the listen
function, except it is church encoded, to make the constraints a little
easier to manage.
passC :: WriterSuitable m a => (a -> w -> w) -> m a -> m a Source #
This is equivalent to the pass
function, except it is church encoded, to make the constraints a little
easier to manage.
MonadWriter w m => MonadWriter w (MaybeT m) Source # | |
(Monoid s, Monad m) => MonadWriter s (WriterT s m) Source # | |
MonadWriter w m => MonadWriter w (IdentityT * m) Source # | |
MonadWriter w m => MonadWriter w (StateT s m) Source # | |
MonadWriter w m => MonadWriter w (StateT s m) Source # | |
MonadWriter w m => MonadWriter w (ExceptT e m) Source # | |
MonadWriter w m => MonadWriter w (ReaderT * r m) Source # | |
A monad transformer similar to WriterT
, except
that it does not leak space. It is implemented using a state monad, so that
mappend
is tail recursive. See
this
email to the Haskell libraries committee for more information.
Wherever possible, coercions are used to eliminate any overhead from the newtype wrapper.
pattern WriterT :: forall m s a. (Functor m, Monoid s, Suitable m (a, s)) => m (a, s) -> WriterT s m a Source #
type Writer s = WriterT s Identity Source #
A type synonym for the plain (non-transformer) version of WriterT
. This
can be used as if it were defined as:
newtype Writer w a = Writer { runWriter :: (a, w) }
runWriterT :: Monoid s => WriterT s m a -> m (a, s) Source #
Run a writer computation in the underlying monad.
execWriterT :: (Monad m, Monoid s, Suitable m s) => WriterT s m a -> m s Source #
Run a writer computation in the underlying monad, and collect its output.
execWriter :: Monoid s => Writer s a -> s Source #
Run a writer computation, and collect its output.
runWriter :: Monoid s => Writer s a -> (a, s) Source #
Run a writer computation.
>>>
runWriter $ traverse (\x -> writer (show x, [x])) [1..5]
(["1","2","3","4","5"],[1,2,3,4,5])
listen :: (MonadWriter w m, WriterSuitable m (a, w)) => m a -> m (a, w) Source #
is an action that executes the action listen
mm
and adds
its output to the value of the computation.
pass :: (MonadWriter w m, Suitable m a, WriterSuitable m (a, w -> w)) => m (a, w -> w) -> m a Source #
is an action that executes the action pass
mm
, which
returns a value and a function, and returns the value, applying
the function to the output.
evalWriterT :: (Monad m, Monoid s, Suitable m a) => WriterT s m a -> m a Source #
Run a writer computation in the underlying monad, and return its result.
evalWriter :: Monoid s => Writer s a -> a Source #
Run a writer computation, and return its result.