Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Strict write-only state
Synopsis
- data Writer w v where
- withWriter :: Monad m => a -> b -> (w -> b -> b) -> m (a, b)
- tell :: Member (Writer w) r => w -> Eff r ()
- censor :: forall w a r. Member (Writer w) r => (w -> w) -> Eff r a -> Eff r a
- runWriter :: (w -> b -> b) -> b -> Eff (Writer w ': r) a -> Eff r (a, b)
- runFirstWriter :: Eff (Writer w ': r) a -> Eff r (a, Maybe w)
- runLastWriter :: Eff (Writer w ': r) a -> Eff r (a, Maybe w)
- runListWriter :: Eff (Writer w ': r) a -> Eff r (a, [w])
- runMonoidWriter :: Monoid w => Eff (Writer w ': r) a -> Eff r (a, w)
- execWriter :: (w -> b -> b) -> b -> Eff (Writer w ': r) a -> Eff r b
- execFirstWriter :: Eff (Writer w ': r) a -> Eff r (Maybe w)
- execLastWriter :: Eff (Writer w ': r) a -> Eff r (Maybe w)
- execListWriter :: Eff (Writer w ': r) a -> Eff r [w]
- execMonoidWriter :: Monoid w => Eff (Writer w ': r) a -> Eff r w
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
Instances
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Writer w ': r)) Source # | |
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. |
Defined in Control.Eff.Writer.Strict 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 # | |
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.
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.