transformers-0.5.6.2: Concrete functor and monad transformers
Copyright(c) Daniel Mendler 2016
(c) Andy Gill 2001
(c) Oregon Graduate Institute of Science and Technology 2001
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Writer.CPS

Description

The strict WriterT monad transformer, which adds collection of outputs (such as a count or string output) to a given monad.

This monad transformer provides only limited access to the output during the computation. For more general access, use Control.Monad.Trans.State instead.

This version builds its output strictly and uses continuation-passing-style to achieve constant space usage. This transformer can be used as a drop-in replacement for Control.Monad.Trans.Writer.Strict.

Synopsis

The Writer monad

type Writer w = WriterT w Identity Source #

A writer monad parameterized by the type w of output to accumulate.

The return function produces the output mempty, while >>= combines the outputs of the subcomputations using mappend.

writer :: (Monoid w, Monad m) => (a, w) -> WriterT w m a Source #

Construct a writer computation from a (result, output) pair. (The inverse of runWriter.)

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.

mapWriter :: (Monoid w, Monoid w') => ((a, w) -> (b, w')) -> Writer w a -> Writer w' b Source #

Map both the return value and output of a computation using the given function.

The WriterT monad transformer

data WriterT w m a Source #

A writer monad parameterized by:

  • w - the output to accumulate.
  • m - The inner monad.

The return function produces the output mempty, while >>= combines the outputs of the subcomputations using mappend.

Instances

Instances details
MonadTrans (WriterT w) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

lift :: Monad m => m a -> WriterT w m a Source #

Monad m => Monad (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

(>>=) :: WriterT w m a -> (a -> WriterT w m b) -> WriterT w m b Source #

(>>) :: WriterT w m a -> WriterT w m b -> WriterT w m b Source #

return :: a -> WriterT w m a Source #

Functor m => Functor (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

fmap :: (a -> b) -> WriterT w m a -> WriterT w m b Source #

(<$) :: a -> WriterT w m b -> WriterT w m a Source #

MonadFix m => MonadFix (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

mfix :: (a -> WriterT w m a) -> WriterT w m a Source #

MonadFail m => MonadFail (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

fail :: String -> WriterT w m a Source #

(Functor m, Monad m) => Applicative (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

pure :: a -> WriterT w m a Source #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b Source #

liftA2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c Source #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b Source #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a Source #

MonadIO m => MonadIO (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

liftIO :: IO a -> WriterT w m a Source #

(Functor m, MonadPlus m) => Alternative (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

empty :: WriterT w m a Source #

(<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

some :: WriterT w m a -> WriterT w m [a] Source #

many :: WriterT w m a -> WriterT w m [a] Source #

(Functor m, MonadPlus m) => MonadPlus (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

mzero :: WriterT w m a Source #

mplus :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

writerT :: (Functor m, Monoid w) => m (a, w) -> WriterT w m a Source #

Construct a writer computation from a (result, output) computation. (The inverse of runWriterT.)

runWriterT :: Monoid w => WriterT w m a -> m (a, w) Source #

Unwrap a writer computation. (The inverse of writerT.)

execWriterT :: (Monad m, Monoid w) => WriterT w m a -> m w Source #

Extract the output from a writer computation.

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.

Writer operations

tell :: (Monoid w, Monad m) => w -> WriterT w m () Source #

tell w is an action that produces the output w.

listen :: (Monoid w, Monad m) => WriterT w m a -> WriterT w m (a, w) Source #

listen m is an action that executes the action m and adds its output to the value of the computation.

listens :: (Monoid w, Monad m) => (w -> b) -> WriterT w m a -> WriterT w m (a, b) Source #

listens f m is an action that executes the action m and adds the result of applying f to the output to the value of the computation.

pass :: (Monoid w, Monoid w', Monad m) => WriterT w m (a, w -> w') -> WriterT w' m a Source #

pass m is an action that executes the action m, which returns a value and a function, and returns the value, applying the function to the output.

censor :: (Monoid w, Monad m) => (w -> w) -> WriterT w m a -> WriterT w m a Source #

censor f m is an action that executes the action m and applies the function f to its output, leaving the return value unchanged.

Lifting other operations

liftCallCC :: CallCC m (a, w) (b, w) -> CallCC (WriterT w m) a b Source #

Uniform lifting of a callCC operation to the new monad. This version rolls back to the original state on entering the continuation.

liftCatch :: Catch e m (a, w) -> Catch e (WriterT w m) a Source #

Lift a catchE operation to the new monad.