effet-0.2.0.0: An Effect System based on Type Classes
Copyright(c) Michael Szvetits 2020
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Writer

Description

The writer effect, similar to the MonadWriter type class from the mtl library.

Lazy and strict interpretations of the effect are available here: Control.Effect.Writer.Lazy and Control.Effect.Writer.Strict.

Synopsis

Tagged Writer Effect

class Monad m => Writer' tag w m | tag m -> w where Source #

An effect that adds a write-only, accumulated output to a given computation.

Methods

tell' :: w -> m () Source #

Produces the output w. In other words, w is appended to the accumulated output.

listen' :: m a -> m (w, a) Source #

Executes a sub-computation and appends w to the accumulated output.

censor' Source #

Arguments

:: (w -> w)

The function which is applied to the output.

-> m a

The sub-computation which produces the modified output.

-> m a

The result of the sub-computation.

Executes a sub-computation and applies the function to its output.

Instances

Instances details
(Monad m, Monoid w) => Writer' (tag :: k) w (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> WriterT w m () Source #

listen' :: WriterT w m a -> WriterT w m (w, a) Source #

censor' :: (w -> w) -> WriterT w m a -> WriterT w m a Source #

(Monad m, Monoid w) => Writer' (tag :: k) w (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> WriterT w m () Source #

listen' :: WriterT w m a -> WriterT w m (w, a) Source #

censor' :: (w -> w) -> WriterT w m a -> WriterT w m a Source #

Writer' tag w m => Writer' (tag :: k) w (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

tell' :: w -> Separation m () Source #

listen' :: Separation m a -> Separation m (w, a) Source #

censor' :: (w -> w) -> Separation m a -> Separation m a Source #

(Monad m, Monoid w) => Writer' (tag :: k) w (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Methods

tell' :: w -> WriterT w m () Source #

listen' :: WriterT w m a -> WriterT w m (w, a) Source #

censor' :: (w -> w) -> WriterT w m a -> WriterT w m a Source #

Handle (Writer' tag w) t m => Writer' (tag :: k) w (EachVia (Writer' tag w ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> EachVia (Writer' tag w ': effs) t m () Source #

listen' :: EachVia (Writer' tag w ': effs) t m a -> EachVia (Writer' tag w ': effs) t m (w, a) Source #

censor' :: (w -> w) -> EachVia (Writer' tag w ': effs) t m a -> EachVia (Writer' tag w ': effs) t m a Source #

Find (Writer' tag w) effs t m => Writer' (tag :: k) w (EachVia (other ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> EachVia (other ': effs) t m () Source #

listen' :: EachVia (other ': effs) t m a -> EachVia (other ': effs) t m (w, a) Source #

censor' :: (w -> w) -> EachVia (other ': effs) t m a -> EachVia (other ': effs) t m a Source #

Control (Writer' tag w) t m => Writer' (tag :: k) w (EachVia ('[] :: [Effect]) t m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> EachVia '[] t m () Source #

listen' :: EachVia '[] t m a -> EachVia '[] t m (w, a) Source #

censor' :: (w -> w) -> EachVia '[] t m a -> EachVia '[] t m a Source #

(Monad m, Monoid w) => Writer' (tag :: k) w (RWST r w s m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> RWST r w s m () Source #

listen' :: RWST r w s m a -> RWST r w s m (w, a) Source #

censor' :: (w -> w) -> RWST r w s m a -> RWST r w s m a Source #

(Monad m, Monoid w) => Writer' (tag :: k) w (RWST r w s m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> RWST r w s m () Source #

listen' :: RWST r w s m a -> RWST r w s m (w, a) Source #

censor' :: (w -> w) -> RWST r w s m a -> RWST r w s m a Source #

(Monad m, Monoid w) => Writer' (tag :: k) w (RWST r w s m) Source # 
Instance details

Defined in Control.Effect.RWS.Strict

Methods

tell' :: w -> RWST r w s m () Source #

listen' :: RWST r w s m a -> RWST r w s m (w, a) Source #

censor' :: (w -> w) -> RWST r w s m a -> RWST r w s m a Source #

Writer' new w m => Writer' (tag :: k2) w (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

tell' :: w -> Tagger tag new m () Source #

listen' :: Tagger tag new m a -> Tagger tag new m (w, a) Source #

censor' :: (w -> w) -> Tagger tag new m a -> Tagger tag new m a Source #

RWS' new r w s m => Writer' (tag :: k2) w (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

tell' :: w -> Tagger tag new m () Source #

listen' :: Tagger tag new m a -> Tagger tag new m (w, a) Source #

censor' :: (w -> w) -> Tagger tag new m a -> Tagger tag new m a Source #

Untagged Writer Effect

If you don't require disambiguation of multiple writer effects (i.e., you only have one writer effect in your monadic context), it is recommended to always use the untagged writer effect.

type Writer w = Writer' G w Source #

tell :: Writer w m => w -> m () Source #

listen :: Writer w m => m a -> m (w, a) Source #

censor :: Writer w m => (w -> w) -> m a -> m a Source #

Convenience Functions

If you don't require disambiguation of multiple writer effects (i.e., you only have one writer effect in your monadic context), it is recommended to always use the untagged functions.

listens' Source #

Arguments

:: forall tag w b m a. Writer' tag w m 
=> (w -> b)

The function which is applied to the output.

-> m a

The sub-computation which produces the modified output.

-> m (b, a)

The result of the sub-computation, including the modified output.

Executes a sub-computation and applies the function to its output, thus adding an additional value to the result of the sub-computation.

listens :: Writer w m => (w -> b) -> m a -> m (b, a) Source #

The untagged version of listens'.

Tagging and Untagging

Conversion functions between the tagged and untagged writer effect, usually used in combination with type applications, like:

    tagWriter' @"newTag" program
    retagWriter' @"oldTag" @"newTag" program
    untagWriter' @"erasedTag" program

tagWriter' :: forall new w m a. Via (Writer' G w) (Tagger G new) m a -> m a Source #

retagWriter' :: forall tag new w m a. Via (Writer' tag w) (Tagger tag new) m a -> m a Source #

untagWriter' :: forall tag w m a. Via (Writer' tag w) (Tagger tag G) m a -> m a Source #