fused-effects-0.1.2.0: A fast, flexible, fused effect system.

Safe HaskellNone
LanguageHaskell2010

Control.Effect.Writer

Synopsis

Documentation

data Writer w (m :: * -> *) k Source #

Constructors

Tell w k 
Instances
Effect (Writer w) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

handle :: Functor f => f () -> (forall x. f (m x) -> n (f x)) -> Writer w m (m a) -> Writer w n (n (f a)) Source #

HFunctor (Writer w) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

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

hmap :: (forall x. m x -> n x) -> Writer w m a -> Writer w n a Source #

Functor (Writer w m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

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

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

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

Defined in Control.Effect.Writer

Methods

ret :: a -> WriterC w m a Source #

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

tell :: (Member (Writer w) sig, Carrier sig m) => w -> m () Source #

Write a value to the log.

fst (run (runWriter (mapM_ (tell . Sum) (0 : ws)))) == foldMap Sum ws

runWriter :: (Carrier sig m, Effect sig, Functor m, Monoid w) => Eff (WriterC w m) a -> m (w, a) Source #

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

run (runWriter (tell (Sum a) *> pure b)) == (Sum a, b)

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

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

run (execWriter (tell (Sum a) *> pure b)) == Sum a

newtype WriterC w m a Source #

Constructors

WriterC 

Fields

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

Defined in Control.Effect.Writer

Methods

ret :: a -> WriterC w m a Source #

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