ether-0.5.1.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Ether.Writer

Contents

Synopsis

MonadWriter class

class (Monoid w, Monad m) => MonadWriter tag w m | m tag -> w where Source #

Methods

writer :: (a, w) -> m a Source #

Embed a simple writer action.

tell :: w -> m () Source #

Append a value to the accumulator within the monad.

listen :: m a -> m (a, w) Source #

Execute an action and add its accumulator to the value of the computation.

pass :: m (a, w -> w) -> m a Source #

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

Instances

(LiftListen t, LiftPass t, Monad (t m), MonadWriter k tag w m, Monoid w) => MonadWriter k tag w (t m) Source # 

Methods

writer :: (a, t m) -> m a Source #

tell :: t m -> m () Source #

listen :: m a -> m (a, t m) Source #

pass :: m (a, t m -> t m) -> m a Source #

(MonadWriter k1 tNew w m, (~) ((* -> *) -> * -> *) trans (IdentityT *)) => MonadWriter k tOld w (TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m) Source # 

Methods

writer :: (a, TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m) -> m a Source #

tell :: TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m -> m () Source #

listen :: m a -> m (a, TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m) Source #

pass :: m (a, TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m -> TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m) -> m a Source #

writer :: MonadWriter tag w m => (a, w) -> m a Source #

Embed a simple writer action.

tell :: MonadWriter tag w m => w -> m () Source #

Append a value to the accumulator within the monad.

listen :: MonadWriter tag w m => m a -> m (a, w) Source #

Execute an action and add its accumulator to the value of the computation.

pass :: MonadWriter tag w m => m (a, w -> w) -> m a Source #

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

listens :: forall tag w m a b. MonadWriter tag w m => (w -> b) -> m a -> m (a, b) Source #

Execute an action and add the result of applying the given function to its accumulator to the value of the computation.

censor :: forall tag w m a. MonadWriter tag w m => (w -> w) -> m a -> m a Source #

Execute an action and apply a function to its accumulator.

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.

runWriter :: forall tag w a. Monoid w => Writer tag w a -> (a, w) Source #

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

execWriter :: forall tag w a. Monoid w => Writer tag w a -> w Source #

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

The WriterT monad transformer

type WriterT tag w = TaggedTrans (TAGGED WRITER tag) (WriterT w) Source #

The writer monad transformer.

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

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

Constructor for computations in the writer monad transformer.

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

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

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

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

The Writer monad (lazy)

type LazyWriter tag w = LazyWriterT 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.

runLazyWriter :: forall tag w a. LazyWriter tag w a -> (a, w) Source #

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

execLazyWriter :: forall tag w a. LazyWriter tag w a -> w Source #

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

The WriterT monad transformer (lazy)

type LazyWriterT tag w = TaggedTrans (TAGGED WRITER tag) (WriterT w) Source #

The writer monad transformer.

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

lazyWriterT :: forall tag w m a. m (a, w) -> LazyWriterT tag w m a Source #

Constructor for computations in the writer monad transformer.

runLazyWriterT :: forall tag w m a. LazyWriterT tag w m a -> m (a, w) Source #

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

execLazyWriterT :: forall tag w m a. Monad m => LazyWriterT tag w m a -> m w Source #

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

MonadWriter class (implicit)

writer' :: forall w m a. MonadWriter' w m => (a, w) -> m a Source #

tell' :: forall w m. MonadWriter' w m => w -> m () Source #

listen' :: forall w m a. MonadWriter' w m => m a -> m (a, w) Source #

pass' :: forall w m a. MonadWriter' w m => m (a, w -> w) -> m a Source #

listens' :: forall w m a b. MonadWriter' w m => (w -> b) -> m a -> m (a, b) Source #

censor' :: forall w m a. MonadWriter' w m => (w -> w) -> m a -> m a Source #

The Writer monad (implicit)

type Writer' w = Writer w w Source #

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

execWriter' :: Monoid w => Writer' w a -> w Source #

The WriterT monad transformer (implicit)

type WriterT' w = WriterT w w Source #

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

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

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

The Writer monad (lazy, implicit)

The WriterT monad transformer (lazy, implicit)

lazyWriterT' :: m (a, w) -> LazyWriterT' w m a Source #

runLazyWriterT' :: LazyWriterT' w m a -> m (a, w) Source #

Internal labels

data TAGGED e t Source #

data WRITER Source #

Encode type-level information for WriterT.

Instances

Monoid w => Handle * * WRITER w (WriterT w) Source # 

Methods

handling :: Monad m => (HandleConstraint WRITER w (WriterT w) p trans m -> r) -> r Source #

Monoid w => Handle * * WRITER w (WriterT w) Source # 

Methods

handling :: Monad m => (HandleConstraint WRITER w (WriterT w) p trans m -> r) -> r Source #

type HandleSuper * * WRITER w trans Source # 
type HandleSuper * * WRITER w trans = Monoid w
type HandleConstraint * * WRITER w trans m Source # 
type HandleConstraint * * WRITER w trans m = MonadWriter w (trans m)