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

Control.Carrier.Writer.Church

Description

A high-performance, strict, church-encoded carrier for Writer.

This carrier issues left-associated mappends, meaning that Monoids such as [] with poor performance for left-associated mappends are ill-suited for use with this carrier. Alternatives such as Endo, Seq, or DList may be preferred.

Since: 1.1.0.0

Synopsis

Writer carrier

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

Run a Writer effect with a Monoidal log, applying a continuation to the final log and result.

runWriter k (pure a) = k mempty a
runWriter k (tell w) = k w ()
runWriter k (listen (tell w)) = k w (w, ())
runWriter k (censor f (tell w)) = k (f w) ()

Since: 1.1.0.0

execWriter :: (Monoid w, Applicative 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 = runWriter (const . pure)

Since: 1.1.0.0

newtype WriterC w m a Source #

Since: 1.1.0.0

Constructors

WriterC (StateC w m a) 

Instances

Instances details
MonadTrans (WriterC w) Source # 
Instance details

Defined in Control.Carrier.Writer.Church

Methods

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

Monad (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Church

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 (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Church

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.Church

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.Church

Methods

fail :: String -> WriterC w m a #

Applicative (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Church

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.Church

Methods

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

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

Defined in Control.Carrier.Writer.Church

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.Church

Methods

mzero :: WriterC w m a #

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

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

Defined in Control.Carrier.Writer.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (WriterC w m) -> (Writer w :+: sig) n a -> ctx () -> WriterC w m (ctx a) Source #

Writer effect