Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The dynamically dispatched variant of the Writer
effect.
Note: unless you plan to change interpretations at runtime, it's recommended to use one of the statically dispatched variants, i.e. Effectful.Writer.Static.Local or Effectful.Writer.Static.Shared.
Synopsis
- data Writer w :: Effect where
- runWriterLocal :: Monoid w => Eff (Writer w : es) a -> Eff es (a, w)
- execWriterLocal :: Monoid w => Eff (Writer w : es) a -> Eff es w
- runWriterShared :: Monoid w => Eff (Writer w : es) a -> Eff es (a, w)
- execWriterShared :: Monoid w => Eff (Writer w : es) a -> Eff es w
- tell :: (HasCallStack, Writer w :> es) => w -> Eff es ()
- listen :: (HasCallStack, Writer w :> es) => Eff es a -> Eff es (a, w)
- listens :: (HasCallStack, Writer w :> es) => (w -> b) -> Eff es a -> Eff es (a, b)
Effect
data Writer w :: Effect where Source #
Provide access to a write only value of type w
.
Instances
type DispatchOf (Writer w) Source # | |
Defined in Effectful.Writer.Dynamic |
Handlers
Local
runWriterLocal :: Monoid w => Eff (Writer w : es) a -> Eff es (a, w) Source #
Run the Writer
effect and return the final value along with the final
output (via Effectful.Writer.Static.Local).
execWriterLocal :: Monoid w => Eff (Writer w : es) a -> Eff es w Source #
Run a Writer
effect and return the final output, discarding the final
value (via Effectful.Writer.Static.Local).
Shared
runWriterShared :: Monoid w => Eff (Writer w : es) a -> Eff es (a, w) Source #
Run the Writer
effect and return the final value along with the final
output (via Effectful.Writer.Static.Shared).
execWriterShared :: Monoid w => Eff (Writer w : es) a -> Eff es w Source #
Run the Writer
effect and return the final output, discarding the final
value (via Effectful.Writer.Static.Shared).
Operations
tell :: (HasCallStack, Writer w :> es) => w -> Eff es () Source #
Append the given output to the overall output of the Writer
.