multistate-0.6.0.0: like mtl's ReaderT / WriterT / StateT, but more than one contained value/type.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.MultiWriter

Contents

Description

The multi-valued version of mtl's Writer / WriterT / MonadWriter

Synopsis

MultiWriterT

newtype MultiWriterT x m a Source

A Writer transformer monad patameterized by:

  • x - The list of types that can be written (Monoid instances).
  • m - The inner monad.

MultiWriterT corresponds to mtl's WriterT, but can contain a heterogenous list of types.

This heterogenous list is represented using Types.Data.List, i.e:

  • '[] - The empty list,
  • a ': b - A list where a is an arbitrary type and b is the rest list.

For example,

MultiWriterT '[Int, Bool] :: (* -> *) -> (* -> *)

is a Writer transformer containing the types [Int, Bool].

Constructors

MultiWriterT 

Fields

runMultiWriterTRaw :: StateT (HList x) m a
 

type MultiWriterTNull = MultiWriterT [] Source

A MultiWriter transformer carrying an empty state.

MonadMultiWriter class

class (Monad m, Monoid a) => MonadMultiWriter a m where Source

Methods

mTell :: a -> m () Source

Instances

run-functions

runMultiWriterT :: (Monoid (HList w), Functor m) => MultiWriterT w m a -> m (a, HList w) Source

runMultiWriterTAW :: (Monoid (HList w), Functor m) => MultiWriterT w m a -> m (a, HList w) Source

runMultiWriterTWA :: (Monoid (HList w), Monad m) => MultiWriterT w m a -> m (HList w, a) Source

with-functions (single Writer)

withMultiWriter :: (Monoid w, Monad m) => MultiWriterT (w : ws) m a -> MultiWriterT ws m (a, w) Source

withMultiWriterAW :: (Monoid w, Monad m) => MultiWriterT (w : ws) m a -> MultiWriterT ws m (a, w) Source

withMultiWriterWA :: (Monoid w, Monad m) => MultiWriterT (w : ws) m a -> MultiWriterT ws m (w, a) Source

withMultiWriterW :: (Monoid w, Monad m) => MultiWriterT (w : ws) m a -> MultiWriterT ws m w Source

with-functions (multiple Writers)

withMultiWriters :: forall w1 w2 m a. (Monoid (HList w1), Monad m, HInit w1) => MultiWriterT (Append w1 w2) m a -> MultiWriterT w2 m (a, HList w1) Source

withMultiWritersAW :: forall w1 w2 m a. (Monoid (HList w1), Monad m, HInit w1) => MultiWriterT (Append w1 w2) m a -> MultiWriterT w2 m (a, HList w1) Source

withMultiWritersWA :: forall w1 w2 m a. (Monoid (HList w1), Monad m, HInit w1) => MultiWriterT (Append w1 w2) m a -> MultiWriterT w2 m (HList w1, a) Source

withMultiWritersW :: forall w1 w2 m a. (Monoid (HList w1), Monad m, HInit w1) => MultiWriterT (Append w1 w2) m a -> MultiWriterT w2 m (HList w1) Source

other functions

mapMultiWriterT :: (m (a, HList w) -> m' (a', HList w)) -> MultiWriterT w m a -> MultiWriterT w m' a' Source

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

mGetRaw :: Monad m => MultiWriterT a m (HList a) Source

A raw extractor of the contained HList (i.e. the complete state).

mPutRaw :: Monad m => HList s -> MultiWriterT s m () Source