transformers-0.5.5.0: Concrete functor and monad transformers

Copyright(c) Nickolay Kudasov 2016
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Accum

Contents

Description

The lazy AccumT monad transformer, which adds accumulation capabilities (such as declarations or document patches) to a given monad.

This monad transformer provides append-only accumulation during the computation. For more general access, use Control.Monad.Trans.State instead.

Synopsis

The Accum monad

type Accum w = AccumT w Identity Source #

An accumulation 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.

accum :: Monad m => (w -> (a, w)) -> AccumT w m a Source #

Construct an accumulation computation from a (result, output) pair. (The inverse of runAccum.)

runAccum :: Accum w a -> w -> (a, w) Source #

Unwrap an accumulation computation as a (result, output) pair. (The inverse of accum.)

execAccum :: Accum w a -> w -> w Source #

Extract the output from an accumulation computation.

evalAccum :: Monoid w => Accum w a -> w -> a Source #

Evaluate an accumulation computation with the given initial output history and return the final value, discarding the final output.

mapAccum :: ((a, w) -> (b, w)) -> Accum w a -> Accum w b Source #

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

The AccumT monad transformer

newtype AccumT w m a Source #

An accumulation 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.

This monad transformer is similar to both state and writer monad transformers. Thus it can be seen as

  • a restricted append-only version of a state monad transformer or
  • a writer monad transformer with the extra ability to read all previous output.

Constructors

AccumT (w -> m (a, w)) 
Instances
Monoid w => MonadTrans (AccumT w) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

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

(Monoid w, Functor m, Monad m) => Monad (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

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

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

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

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

Functor m => Functor (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

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

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

(Monoid w, Functor m, MonadFix m) => MonadFix (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

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

(Monoid w, MonadFail m) => MonadFail (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

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

(Monoid w, Functor m, Monad m) => Applicative (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

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

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

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

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

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

(Monoid w, Functor m, MonadIO m) => MonadIO (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

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

(Monoid w, Functor m, MonadPlus m) => Alternative (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

empty :: AccumT w m a Source #

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

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

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

(Monoid w, Functor m, MonadPlus m) => MonadPlus (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

mzero :: AccumT w m a Source #

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

runAccumT :: AccumT w m a -> w -> m (a, w) Source #

Unwrap an accumulation computation.

execAccumT :: Monad m => AccumT w m a -> w -> m w Source #

Extract the output from an accumulation computation.

evalAccumT :: (Monad m, Monoid w) => AccumT w m a -> w -> m a Source #

Evaluate an accumulation computation with the given initial output history and return the final value, discarding the final output.

mapAccumT :: (m (a, w) -> n (b, w)) -> AccumT w m a -> AccumT w n b Source #

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

Accum operations

look :: (Monoid w, Monad m) => AccumT w m w Source #

look is an action that fetches all the previously accumulated output.

looks :: (Monoid w, Monad m) => (w -> a) -> AccumT w m a Source #

look is an action that retrieves a function of the previously accumulated output.

add :: Monad m => w -> AccumT w m () Source #

add w is an action that produces the output w.

Lifting other operations

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

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

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

In-situ lifting of a callCC operation to the new monad. This version uses the current output history on entering the continuation. It does not satisfy the uniformity property (see Control.Monad.Signatures).

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

Lift a catchE operation to the new monad.

liftListen :: Monad m => Listen w m (a, s) -> Listen w (AccumT s m) a Source #

Lift a listen operation to the new monad.

liftPass :: Monad m => Pass w m (a, s) -> Pass w (AccumT s m) a Source #

Lift a pass operation to the new monad.

Monad transformations

readerToAccumT :: (Functor m, Monoid w) => ReaderT w m a -> AccumT w m a Source #

Convert a read-only computation into an accumulation computation.

writerToAccumT :: WriterT w m a -> AccumT w m a Source #

Convert a writer computation into an accumulation computation.

accumToStateT :: (Functor m, Monoid s) => AccumT s m a -> StateT s m a Source #

Convert an accumulation (append-only) computation into a fully stateful computation.