writer-cps-transformers-0.1.0.1: WriteT and RWST monad transformers

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Writer.CPS

Contents

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

MonadTrans (WriterT w) Source # 

Methods

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

Monad m => Monad (WriterT w m) Source # 

Methods

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

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

return :: a -> WriterT w m a #

fail :: String -> WriterT w m a #

Functor m => Functor (WriterT w m) Source # 

Methods

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

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

MonadFix m => MonadFix (WriterT w m) Source # 

Methods

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

MonadFail m => MonadFail (WriterT w m) Source # 

Methods

fail :: String -> WriterT w m a #

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

Methods

pure :: a -> WriterT w m a #

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

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

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

MonadIO m => MonadIO (WriterT w m) Source # 

Methods

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

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

Methods

empty :: WriterT w m a #

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

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

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

(Functor m, MonadPlus m) => MonadPlus (WriterT w m) Source # 

Methods

mzero :: WriterT w m a #

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

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

Unwrap a writer computation.

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.