dunai-0.6.0: Generalised reactive framework supporting classic, arrowized and monadic FRP.

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.MSF.Writer

Contents

Description

MSFs with a Writer monadic layer.

This module contains functions to work with MSFs that include a Writer monadic layer. This includes functions to create new MSFs that include an additional layer, and functions to flatten that layer out of the MSF's transformer stack.

It is based on the _strict_ writer monad Strict, so when combining it with other modules such as mtl's, the strict version has to be included, i.e. Strict instead of Writer or Lazy.

Synopsis

Documentation

newtype WriterT w (m :: Type -> Type) a #

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.

Constructors

WriterT 

Fields

Instances
(Monoid w, MonadSplit g m) => MonadSplit g (WriterT w m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getSplit :: WriterT w m g #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> WriterT w m α #

Monoid w => MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

(Monoid w, Monad m) => Monad (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

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) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

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

(Monoid w, MonadFix m) => MonadFix (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

(Monoid w, MonadFail m) => MonadFail (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

fail :: String -> WriterT w m a #

(Monoid w, Applicative m) => Applicative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

pure :: a -> WriterT w m a #

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

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

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

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

Foldable f => Foldable (WriterT w f) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

fold :: Monoid m => WriterT w f m -> m #

foldMap :: Monoid m => (a -> m) -> WriterT w f a -> m #

foldr :: (a -> b -> b) -> b -> WriterT w f a -> b #

foldr' :: (a -> b -> b) -> b -> WriterT w f a -> b #

foldl :: (b -> a -> b) -> b -> WriterT w f a -> b #

foldl' :: (b -> a -> b) -> b -> WriterT w f a -> b #

foldr1 :: (a -> a -> a) -> WriterT w f a -> a #

foldl1 :: (a -> a -> a) -> WriterT w f a -> a #

toList :: WriterT w f a -> [a] #

null :: WriterT w f a -> Bool #

length :: WriterT w f a -> Int #

elem :: Eq a => a -> WriterT w f a -> Bool #

maximum :: Ord a => WriterT w f a -> a #

minimum :: Ord a => WriterT w f a -> a #

sum :: Num a => WriterT w f a -> a #

product :: Num a => WriterT w f a -> a #

Traversable f => Traversable (WriterT w f) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

traverse :: Applicative f0 => (a -> f0 b) -> WriterT w f a -> f0 (WriterT w f b) #

sequenceA :: Applicative f0 => WriterT w f (f0 a) -> f0 (WriterT w f a) #

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

sequence :: Monad m => WriterT w f (m a) -> m (WriterT w f a) #

(Monoid w, MonadPlus m) => MonadPlus (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

mzero :: WriterT w m a #

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

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

(MonadRandom m, Monoid w) => MonadRandom (WriterT w m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomR :: Random a => (a, a) -> WriterT w m a #

getRandom :: Random a => WriterT w m a #

getRandomRs :: Random a => (a, a) -> WriterT w m [a] #

getRandoms :: Random a => WriterT w m [a] #

(Monoid w, MonadInterleave m) => MonadInterleave (WriterT w m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

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

Contravariant m => Contravariant (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

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

(Eq w, Eq1 m) => Eq1 (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

(Ord w, Ord1 m) => Ord1 (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

(Read w, Read1 m) => Read1 (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (WriterT w m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [WriterT w m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (WriterT w m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [WriterT w m a] #

(Show w, Show1 m) => Show1 (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> WriterT w m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [WriterT w m a] -> ShowS #

(Monoid w, MonadZip m) => MonadZip (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

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

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

(Monoid w, Alternative m) => Alternative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

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] #

(Eq w, Eq1 m, Eq a) => Eq (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

(/=) :: WriterT w m a -> WriterT w m a -> Bool #

(Ord w, Ord1 m, Ord a) => Ord (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

compare :: WriterT w m a -> WriterT w m a -> Ordering #

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

(<=) :: WriterT w m a -> WriterT w m a -> Bool #

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

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

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

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

(Read w, Read1 m, Read a) => Read (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

readsPrec :: Int -> ReadS (WriterT w m a) #

readList :: ReadS [WriterT w m a] #

readPrec :: ReadPrec (WriterT w m a) #

readListPrec :: ReadPrec [WriterT w m a] #

(Show w, Show1 m, Show a) => Show (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

showsPrec :: Int -> WriterT w m a -> ShowS #

show :: WriterT w m a -> String #

showList :: [WriterT w m a] -> ShowS #

type Writer w = WriterT w Identity #

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.

runWriter :: Writer w a -> (a, w) #

Unwrap a writer computation as a (result, output) pair. (The inverse of writer.)

execWriter :: Writer w a -> w #

Extract the output from a writer computation.

mapWriter :: ((a, w) -> (b, w')) -> Writer w a -> Writer w' b #

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

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

Extract the output from a writer computation.

mapWriterT :: (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b #

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

censor :: Monad m => (w -> w) -> WriterT w m a -> WriterT w m a #

censor f m is an action that executes the action m and applies the function f to its output, leaving the return value unchanged.

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

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.

listen :: Monad m => WriterT w m a -> WriterT w m (a, w) #

listen m is an action that executes the action m and adds its output to the value of the computation.

tell :: Monad m => w -> WriterT w m () #

tell w is an action that produces the output w.

writer :: Monad m => (a, w) -> WriterT w m a #

Construct a writer computation from a (result, output) pair. (The inverse of runWriter.)

Writer MSF running and wrapping

writerS :: (Functor m, Monad m, Monoid w) => MSF m a (w, b) -> MSF (WriterT w m) a b Source #

Build an MSF in the Writer monad from one that produces the log as an extra output. This is the opposite of runWriterS.

runWriterS :: (Functor m, Monad m) => MSF (WriterT s m) a b -> MSF m a (s, b) Source #

Build an MSF that produces the log as an extra output from one on the Writer monad. This is the opposite of writerS.