ether-0.2.0.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Ether.Writer

Contents

Description

Synopsis

The Writer monad

type Writer tag w = WriterT tag w Identity Source

The parametrizable writer monad.

Computations can accumulate a monoid value.

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

writer :: Monad m => proxy tag -> (a, w) -> WriterT tag w m a Source

Constructor for computations in the writer monad (the inverse of runWriter).

runWriter :: proxy tag -> Writer tag w a -> (a, w) Source

Runs a Writer and returns both the normal value and the final accumulator.

execWriter :: proxy tag -> Writer tag w a -> w Source

Runs a Writer and returns the final accumulator, discarding the normal value.

The WriterT monad transformer

data WriterT tag w m a Source

The writer monad transformer.

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

Instances

(Monoid w, MonadReader tag r m) => MonadReader tag r (WriterT tag' w m) 
(Monoid w, MonadState tag s m) => MonadState tag s (WriterT tag' w m) 
(Monoid w, MonadExcept tag e m) => MonadExcept tag e (WriterT tag' w m) 
(Monoid w', MonadWriter tag w m) => MonadWriter tag w (WriterT tag' w' m) 
(Monoid w, Monad m) => MonadWriter tag w (WriterT tag w m) 
(Monoid w, MonadError e m) => MonadError e (WriterT tag w m) 
(Monoid w, MonadReader r m) => MonadReader r (WriterT tag w m) 
(Monoid w, MonadState s m) => MonadState s (WriterT tag w m) 
(Monoid w, MonadWriter w' m) => MonadWriter w' (WriterT tag w m) 
Monoid w => MonadTrans (WriterT tag w) 
(Alternative m, Monoid w) => Alternative (WriterT tag w m) 
(Monad m, Monoid w) => Monad (WriterT tag w m) 
Functor m => Functor (WriterT tag w m) 
(MonadFix m, Monoid w) => MonadFix (WriterT tag w m) 
(MonadPlus m, Monoid w) => MonadPlus (WriterT tag w m) 
(Applicative m, Monoid w) => Applicative (WriterT tag w m) 
(Monoid w, MonadIO m) => MonadIO (WriterT tag w m) 
(Monoid w, MonadCont m) => MonadCont (WriterT tag w m) 
Taggable (WriterT tag w m) 
Tagged (WriterT tag w m) tag 
Generic (WriterT tag w m a) 
Newtype (WriterT tag w m a) 
type Untagged (WriterT tag w m) = WriterT w m 
type Tag (WriterT tag w m) = Just * tag 
type Inner (WriterT tag w m) = Just (* -> *) m 
type Rep (WriterT tag w m a) 
type O (WriterT tag w m a) = GO (Rep (WriterT tag w m a)) 

writerT :: proxy tag -> m (a, w) -> WriterT tag w m a Source

Constructor for computations in the writer monad transformer.

runWriterT :: proxy tag -> WriterT tag w m a -> m (a, w) Source

Runs a WriterT and returns both the normal value and the final accumulator.

execWriterT :: Monad m => proxy tag -> WriterT tag w m a -> m w Source

Runs a WriterT and returns the final accumulator, discarding the normal value.

mapWriterT :: proxy tag -> (m (a, w) -> n (b, w')) -> WriterT tag w m a -> WriterT tag w' n b Source

Transform the computation inside a WriterT.

Writer operations

tell :: Monad m => proxy tag -> w -> WriterT tag w m () Source

Appends a value to the accumulator within the monad.

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

Executes an action and adds its accumulator to the value of the computation.

pass :: (Monoid w, Monad m) => proxy tag -> WriterT tag w m (a, w -> w) -> WriterT tag w m a Source

Executes an action which returns a value and a function, and returns the value, applying the function to the accumulator.

Lifting other operations

liftCallCC :: Monoid w => proxy tag -> CallCC m (a, w) (b, w) -> CallCC (WriterT tag w m) a b Source

Lift a callCC operation to the new monad.

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

Lift a catchE operation to the new monad.

liftListen :: Monad m => proxy tag -> Listen w' m (a, w) -> Listen w' (WriterT tag w m) a Source

Lift a listen operation to the new monad.

liftPass :: Monad m => proxy tag -> Pass w' m (a, w) -> Pass w' (WriterT tag w m) a Source

Lift a pass operation to the new monad.