fused-effects-1.0.0.1: A fast, flexible, fused effect system.
Safe HaskellNone
LanguageHaskell2010

Control.Carrier.Writer.Strict

Description

A carrier for Writer effects. This carrier performs its append operations strictly and thus avoids the space leaks inherent in lazy writer monads. These appends are left-associative; as such, [] is a poor choice of monoid for computations that entail many calls to tell. The Seq or DList monoids may be a superior choice.

This implementation is based on a post Gabriel Gonzalez made to the Haskell mailing list: https://mail.haskell.org/pipermail/libraries/2013-March/019528.html

Since: 1.0.0.0

Synopsis

Writer carrier

runWriter :: Monoid w => WriterC w m a -> m (w, a) Source #

Run a Writer effect with a Monoidal log, producing the final log alongside the result value.

runWriter (tell w) = pure (w, ())
runWriter (pure a) = pure (mempty, a)

execWriter :: (Monoid w, Functor m) => WriterC w m a -> m w Source #

Run a Writer effect with a Monoidal log, producing the final log and discarding the result value.

execWriter m = fmap fst (runWriter m)

newtype WriterC w m a Source #

A space-efficient carrier for Writer effects, implemented atop Control.Carrier.State.Strict.

Since: 1.0.0.0

Constructors

WriterC (StateC w m a) 

Instances

Instances details
MonadTrans (WriterC w) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

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

Monad m => Monad (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

(>>=) :: WriterC w m a -> (a -> WriterC w m b) -> WriterC w m b #

(>>) :: WriterC w m a -> WriterC w m b -> WriterC w m b #

return :: a -> WriterC w m a #

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

Defined in Control.Carrier.Writer.Strict

Methods

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

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

MonadFix m => MonadFix (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

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

MonadFail m => MonadFail (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

fail :: String -> WriterC w m a #

Monad m => Applicative (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

pure :: a -> WriterC w m a #

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

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

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

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

MonadIO m => MonadIO (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

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

(Alternative m, Monad m) => Alternative (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

empty :: WriterC w m a #

(<|>) :: WriterC w m a -> WriterC w m a -> WriterC w m a #

some :: WriterC w m a -> WriterC w m [a] #

many :: WriterC w m a -> WriterC w m [a] #

(Alternative m, Monad m) => MonadPlus (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

mzero :: WriterC w m a #

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

(Monoid w, Algebra sig m, Effect sig) => Algebra (Writer w :+: sig) (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

alg :: (Writer w :+: sig) (WriterC w m) a -> WriterC w m a Source #

Writer effect