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

Description

Strict interpretations of the Writer' effect.

If you don't require disambiguation of multiple writer effects (i.e., you only have one writer effect in your monadic context), you usually need the untagged interpretations.

Synopsis

Interpreter Type

data WriterT w m a Source #

The strict interpreter of the writer effect. This type implements the Writer' type class in a strict manner.

When interpreting the effect, you usually don't interact with this type directly, but instead use one of its corresponding interpretation functions.

Instances

Instances details
(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 #

MonadBase b m => MonadBase b (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Methods

liftBase :: b α -> WriterT w m α #

(MonadBaseControl b m, Monoid w) => MonadBaseControl b (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Associated Types

type StM (WriterT w m) a #

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

MonadTrans (WriterT w) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Methods

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

Monoid w => MonadTransControl (WriterT w) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Associated Types

type StT (WriterT w) a #

Methods

liftWith :: Monad m => (Run (WriterT w) -> m a) -> WriterT w m a #

restoreT :: Monad m => m (StT (WriterT w) a) -> WriterT w m a #

Monad m => Monad (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Methods

(>>=) :: WriterT w m a -> (a -> WriterT w m b) -> WriterT w m b #

(>>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

return :: a -> WriterT w m a #

Functor m => Functor (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Methods

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

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

Monad m => Applicative (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

liftA2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

MonadIO m => MonadIO (WriterT w m) Source # 
Instance details

Defined in Control.Effect.Writer.Strict

Methods

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

type StT (WriterT w) a Source # 
Instance details

Defined in Control.Effect.Writer.Strict

type StT (WriterT w) a = (a, w)
type StM (WriterT w m) a Source # 
Instance details

Defined in Control.Effect.Writer.Strict

type StM (WriterT w m) a = ComposeSt (WriterT w) m a

Tagged Interpretations

execWriter' Source #

Arguments

:: forall tag w m a. (Monad m, Monoid w) 
=> (Writer' tag w `Via` WriterT w) m a

The program whose writer effect should be handled.

-> m w

The program with its writer effect handled, producing the final output w.

Runs the writer effect and returns the final output.

runWriter' Source #

Arguments

:: forall tag w m a. (Functor m, Monoid w) 
=> (Writer' tag w `Via` WriterT w) m a

The program whose writer effect should be handled.

-> m (w, a)

The program with its writer effect handled, producing the final output w and the result a.

Runs the writer effect and returns both the final output and the result of the interpreted program.

Untagged Interpretations

execWriter :: (Monad m, Monoid w) => (Writer w `Via` WriterT w) m a -> m w Source #

The untagged version of execWriter'.

runWriter :: (Functor m, Monoid w) => (Writer w `Via` WriterT w) m a -> m (w, a) Source #

The untagged version of runWriter'.