| Copyright | (c) Andy Gill 2001 (c) Oregon Graduate Institute of Science and Technology 2001 | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | experimental | 
| Portability | non-portable (multi-param classes, functional dependencies) | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Control.Monad.Writer.CPS
Description
Strict writer monads that use continuation-passing-style to achieve constant space usage.
Inspired by the paper Functional Programming with Overloading and Higher-Order Polymorphism, Mark P Jones (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html) Advanced School of Functional Programming, 1995.
Since: mtl-2.3, transformers-0.5.6
Synopsis
- class (Monoid w, Monad m) => MonadWriter w (m :: Type -> Type) | m -> w where
- listens :: MonadWriter w m => (w -> b) -> m a -> m (a, b)
- censor :: MonadWriter w m => (w -> w) -> m a -> m a
- type Writer w = WriterT w Identity
- runWriter :: Monoid w => Writer w a -> (a, w)
- execWriter :: Monoid w => Writer w a -> w
- mapWriter :: (Monoid w, Monoid w') => ((a, w) -> (b, w')) -> Writer w a -> Writer w' b
- data WriterT w (m :: Type -> Type) a
- execWriterT :: (Monad m, Monoid w) => WriterT w m a -> m w
- mapWriterT :: (Monad n, Monoid w, Monoid w') => (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
- module Control.Monad.Trans
MonadWriter class
class (Monoid w, Monad m) => MonadWriter w (m :: Type -> Type) | m -> w where Source #
Methods
writer :: (a, w) -> m a Source #
writer (a,w)
tell ww.
listen :: m a -> m (a, w) Source #
listen mm and adds
 its output to the value of the computation.
pass :: m (a, w -> w) -> m a Source #
pass mm, which
 returns a value and a function, and returns the value, applying
 the function to the output.
Instances
| MonadWriter w m => MonadWriter w (MaybeT m) Source # | |
| Monoid w => MonadWriter w ((,) w) Source # | Since: mtl-2.2.2 | 
| (Monoid w', MonadWriter w m) => MonadWriter w (AccumT w' m) Source # | There are two valid instances for  
 This instance chooses (1), reflecting that the intent
   of  Since: mtl-2.3 | 
| MonadWriter w m => MonadWriter w (ExceptT e m) Source # | Since: mtl-2.2 | 
| MonadWriter w m => MonadWriter w (IdentityT m) Source # | |
| MonadWriter w m => MonadWriter w (ReaderT r m) Source # | |
| MonadWriter w m => MonadWriter w (StateT s m) Source # | |
| MonadWriter w m => MonadWriter w (StateT s m) Source # | |
| (Monoid w, Monad m) => MonadWriter w (WriterT w m) Source # | Since: mtl-2.3 | 
| (Monoid w, Monad m) => MonadWriter w (WriterT w m) Source # | |
| (Monoid w, Monad m) => MonadWriter w (WriterT w m) Source # | |
| (Monoid w, Monad m) => MonadWriter w (RWST r w s m) Source # | Since: mtl-2.3 | 
| (Monoid w, Monad m) => MonadWriter w (RWST r w s m) Source # | |
| (Monoid w, Monad m) => MonadWriter w (RWST r w s m) Source # | |
listens :: MonadWriter w m => (w -> b) -> m a -> m (a, b) Source #
censor :: MonadWriter w m => (w -> w) -> m a -> m a Source #
The Writer monad
runWriter :: Monoid w => Writer w a -> (a, w) Source #
Unwrap a writer computation as a (result, output) pair.
 (The inverse of writer.)
execWriter :: Monoid w => Writer w a -> w Source #
Extract the output from a writer computation.
- execWriterm =- snd(- runWriterm)
The WriterT monad transformer
data WriterT w (m :: Type -> Type) a Source #
A writer monad parameterized by:
- w- the output to accumulate.
- m- The inner monad.
The return function produces the output mempty, while m 
 combines the outputs of the subcomputations using >>= kmappend (also
 known as <>):
Instances
| MonadAccum w' m => MonadAccum w' (WriterT w m) Source # | Since: mtl-2.3 | ||||
| (Monoid w, MonadError e m) => MonadError e (WriterT w m) Source # | Since: mtl-2.3 | ||||
| Defined in Control.Monad.Error.Class Methods throwError :: e -> WriterT w m a Source # catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source # | |||||
| (Monoid w, MonadReader r m) => MonadReader r (WriterT w m) Source # | Since: mtl-2.3 | ||||
| MonadSelect w' m => MonadSelect w' (WriterT w m) Source # | 'Readerizes' the writer: the 'ranking' function can see the value
 that's been accumulated (of type  Since: mtl-2.3 | ||||
| Defined in Control.Monad.Select | |||||
| (Monoid w, MonadState s m) => MonadState s (WriterT w m) Source # | Since: mtl-2.3 | ||||
| (Monoid w, Monad m) => MonadWriter w (WriterT w m) Source # | Since: mtl-2.3 | ||||
| MonadTrans (WriterT w) Source # | |||||
| (Functor m, MonadPlus m) => Alternative (WriterT w m) Source # | |||||
| (Functor m, Monad m) => Applicative (WriterT w m) Source # | |||||
| Defined in Control.Monad.Trans.Writer.CPS | |||||
| Functor m => Functor (WriterT w m) Source # | |||||
| Monad m => Monad (WriterT w m) Source # | |||||
| (Functor m, MonadPlus m) => MonadPlus (WriterT w m) Source # | |||||
| MonadFail m => MonadFail (WriterT w m) Source # | |||||
| Defined in Control.Monad.Trans.Writer.CPS Methods fail :: HasCallStack => String -> WriterT w m a # | |||||
| MonadFix m => MonadFix (WriterT w m) Source # | |||||
| Defined in Control.Monad.Trans.Writer.CPS | |||||
| MonadIO m => MonadIO (WriterT w m) Source # | |||||
| Defined in Control.Monad.Trans.Writer.CPS | |||||
| (Monoid w, MonadCont m) => MonadCont (WriterT w m) Source # | Since: mtl-2.3 | ||||
| Generic (WriterT w m a) Source # | |||||
| Defined in Control.Monad.Trans.Writer.CPS Associated Types 
 | |||||
| type Rep (WriterT w m a) Source # | |||||
| Defined in Control.Monad.Trans.Writer.CPS | |||||
execWriterT :: (Monad m, Monoid w) => WriterT w m a -> m w Source #
Extract the output from a writer computation.
- execWriterTm =- liftM- snd(- runWriterTm)
mapWriterT :: (Monad n, Monoid w, Monoid w') => (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b Source #
Map both the return value and output of a computation using the given function.
- runWriterT(- mapWriterTf m) = f (- runWriterTm)
module Control.Monad.Trans