strict-writer-0.4.0.0: A stricter writer, which uses StateT in order to avoid space leaks.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Writer.Stricter

Contents

Description

This module provides monad transformer similar to WriterT, implemented using StateT, making it tail recursive. (The traditional writer always leaks space: see here for more information).

Pattern Synonyms are used to provide the same interface as WriterT. Unfortunately, current GHC warns whenever these patterns are used that there are unmatched patterns: the COMPLETE pragma should solve this problem in future version of GHC.

A pattern synonym is also provided for a non-transformer version of writer. Again, this is just StateT underneath, but its interface looks as if it was defined like so:

newtype Writer w a = Writer { runWriter :: (a, w) }

Synopsis

Transformer

data WriterT s m a Source #

A monad transformer similar to WriterT, except that it does not leak space. It is implemented using a state monad, so that mappend is tail recursive. See this email to the Haskell libraries committee for more information.

Wherever possible, coercions are used to eliminate any overhead from the newtype wrapper.

Instances

MonadState s m => MonadState s (WriterT w m) Source # 

Methods

get :: WriterT w m s

put :: s -> WriterT w m ()

state :: (s -> (a, s)) -> WriterT w m a

MonadError e m => MonadError e (WriterT s m) Source # 

Methods

throwError :: e -> WriterT s m a

catchError :: WriterT s m a -> (e -> WriterT s m a) -> WriterT s m a

MonadReader r m => MonadReader r (WriterT s m) Source # 

Methods

ask :: WriterT s m r

local :: (r -> r) -> WriterT s m a -> WriterT s m a

reader :: (r -> a) -> WriterT s m a

(Monoid s, Monad m) => MonadWriter s (WriterT s m) Source # 

Methods

writer :: (a, s) -> WriterT s m a

tell :: s -> WriterT s m ()

listen :: WriterT s m a -> WriterT s m (a, s)

pass :: WriterT s m (a, s -> s) -> WriterT s m a

MonadTrans (WriterT s) Source # 

Methods

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

Monad m => Monad (WriterT s m) Source # 

Methods

(>>=) :: WriterT s m a -> (a -> WriterT s m b) -> WriterT s m b #

(>>) :: WriterT s m a -> WriterT s m b -> WriterT s m b #

return :: a -> WriterT s m a #

fail :: String -> WriterT s m a #

Functor m => Functor (WriterT s m) Source # 

Methods

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

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

MonadFix m => MonadFix (WriterT s m) Source # 

Methods

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

MonadFail m => MonadFail (WriterT s m) Source # 

Methods

fail :: String -> WriterT s m a #

Monad m => Applicative (WriterT s m) Source # 

Methods

pure :: a -> WriterT s m a #

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

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

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

(Foldable m, Monoid w) => Foldable (WriterT w m) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: WriterT w m a -> Bool #

length :: WriterT w m a -> Int #

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

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

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

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

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

(Traversable m, Monoid w) => Traversable (WriterT w m) Source # 

Methods

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

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

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

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

(Eq1 m, Eq w, Monoid w) => Eq1 (WriterT w m) Source # 

Methods

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

(Ord1 m, Ord w, Monoid w) => Ord1 (WriterT w m) Source # 

Methods

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

(Read w, Read1 m, Monoid w, Functor m) => Read1 (WriterT w m) Source # 

Methods

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

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

(Show w, Show1 m, Monoid w) => Show1 (WriterT w m) Source # 

Methods

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

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

MonadIO m => MonadIO (WriterT s m) Source # 

Methods

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

MonadPlus m => Alternative (WriterT s m) Source # 

Methods

empty :: WriterT s m a #

(<|>) :: WriterT s m a -> WriterT s m a -> WriterT s m a #

some :: WriterT s m a -> WriterT s m [a] #

many :: WriterT s m a -> WriterT s m [a] #

MonadPlus m => MonadPlus (WriterT s m) Source # 

Methods

mzero :: WriterT s m a #

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

MonadCont m => MonadCont (WriterT s m) Source # 

Methods

callCC :: ((a -> WriterT s m b) -> WriterT s m a) -> WriterT s m a

(Eq w, Eq1 m, Eq a, Monoid w) => Eq (WriterT w m a) Source # 

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, Monoid w) => Ord (WriterT w m a) Source # 

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, Monoid w, Functor m) => Read (WriterT w m a) Source # 

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, Monoid w) => Show (WriterT w m a) Source # 

Methods

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

show :: WriterT w m a -> String #

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

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

Run a writer computation in the underlying monad.

pattern WriterT :: forall m s a. (Functor m, Monoid s) => m (a, s) -> WriterT s m a Source #

This pattern gives the newtype wrapper around StateT the same interface as WriterT. Unfortunately, GHC currently warns that a function is incomplete wherever this pattern is used. This issue should be solved in a future version of GHC, when the COMPLETE pragma is implemented.

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

Run a writer computation in the underlying monad, and collect its output.

evalWriterT :: (Monad m, Monoid s) => WriterT s m a -> m a Source #

Run a writer computation in the underlying monad, and return its result.

Plain

type Writer s = WriterT s Identity Source #

A type synonym for the plain (non-transformer) version of WriterT. This can be used as if it were defined as:

newtype Writer w a = Writer { runWriter :: (a, w) }

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

Run a writer computation.

>>> runWriter $ traverse (\x -> Writer (show x, [x])) [1..5]
(["1","2","3","4","5"],[1,2,3,4,5])

pattern Writer :: forall s a. Monoid s => (a, s) -> Writer s a Source #

This pattern gives the newtype wrapper around StateT the same interface as as if it was defined like so:

newtype Writer w a = Writer { runWriter :: (a, w) }

Unfortunately GHC warns that a function is incomplete wherever this pattern is used. This issue should be solved in a future version of GHC, when the COMPLETE pragma is implemented.

>>> execWriter $ traverse (\x -> Writer (x, [x])) [1..5]
[1,2,3,4,5]

execWriter :: Monoid s => Writer s a -> s Source #

Run a writer computation, and collect its output.

evalWriter :: Monoid s => Writer s a -> a Source #

Run a writer computation, and return its result.