extensible-effects-5.0.0.0: An Alternative to Monad Transformers

Safe HaskellSafe
LanguageHaskell2010

Control.Eff.Writer.Strict

Description

Strict write-only state

Synopsis

Documentation

data Writer w v where Source #

The Writer monad

In MTL's Writer monad, the told value must have a |Monoid| type. Our writer has no such constraints. If we write a |Writer|-like interpreter to accumulate the told values in a monoid, it will have the |Monoid w| constraint then

Constructors

Tell :: !w -> Writer w () 
Instances
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Writer w ': r)) Source # 
Instance details

Defined in Control.Eff.Writer.Strict

Associated Types

type StM (Eff (Writer w ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Writer w ': r)) m -> m a) -> Eff (Writer w ': r) a #

restoreM :: StM (Eff (Writer w ': r)) a -> Eff (Writer w ': r) a #

Monad m => Handle (Writer w) r a (b -> (w -> b -> b) -> m (a, b)) Source #

Given a value to write, and a callback (which includes empty and append), respond to requests.

Instance details

Defined in Control.Eff.Writer.Strict

Methods

handle :: (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Arrs r v a -> Writer w v -> b -> (w -> b -> b) -> m (a, b) Source #

handle_relay :: (r ~ (Writer w ': r'), Relay (b -> (w -> b -> b) -> m (a, b)) r') => (a -> b -> (w -> b -> b) -> m (a, b)) -> (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Eff r a -> b -> (w -> b -> b) -> m (a, b) Source #

respond_relay :: (a -> b -> (w -> b -> b) -> m (a, b)) -> (Eff r a -> b -> (w -> b -> b) -> m (a, b)) -> Eff r a -> b -> (w -> b -> b) -> m (a, b) Source #

type StM (Eff (Writer w ': r)) a Source # 
Instance details

Defined in Control.Eff.Writer.Strict

type StM (Eff (Writer w ': r)) a = StM (Eff r) (a, [w])

withWriter :: Monad m => a -> b -> (w -> b -> b) -> m (a, b) Source #

How to interpret a pure value in a writer context, given the value for mempty.

tell :: Member (Writer w) r => w -> Eff r () Source #

Write a new value.

censor :: forall w a r. Member (Writer w) r => (w -> w) -> Eff r a -> Eff r a Source #

Transform the state being produced.

runWriter :: (w -> b -> b) -> b -> Eff (Writer w ': r) a -> Eff r (a, b) Source #

Handle Writer requests, using a user-provided function to accumulate values, hence no Monoid constraints.

runFirstWriter :: Eff (Writer w ': r) a -> Eff r (a, Maybe w) Source #

Handle Writer requests by taking the first value provided.

runLastWriter :: Eff (Writer w ': r) a -> Eff r (a, Maybe w) Source #

Handle Writer requests by overwriting previous values.

runListWriter :: Eff (Writer w ': r) a -> Eff r (a, [w]) Source #

Handle Writer requests, using a List to accumulate values.

runMonoidWriter :: Monoid w => Eff (Writer w ': r) a -> Eff r (a, w) Source #

Handle Writer requests, using a Monoid instance to accumulate values.

execWriter :: (w -> b -> b) -> b -> Eff (Writer w ': r) a -> Eff r b Source #

Handle Writer requests, using a user-provided function to accumulate values and returning the final accumulated values.

execFirstWriter :: Eff (Writer w ': r) a -> Eff r (Maybe w) Source #

Handle Writer requests by taking the first value provided and and returning the final accumulated values.

execLastWriter :: Eff (Writer w ': r) a -> Eff r (Maybe w) Source #

Handle Writer requests by overwriting previous values and returning the final accumulated values.

execListWriter :: Eff (Writer w ': r) a -> Eff r [w] Source #

Handle Writer requests, using a List to accumulate values and returning the final accumulated values.

execMonoidWriter :: Monoid w => Eff (Writer w ': r) a -> Eff r w Source #

Handle Writer requests, using a Monoid instance to accumulate values and returning the final accumulated values.