Safe Haskell | None |
---|---|
Language | Haskell2010 |
Effectful.Writer.Dynamic
Description
The dynamically dispatched variant of the Writer
effect.
Note: unless you plan to change interpretations at runtime or you need the
MonadWriter
instance for compatibility with existing
code, 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 (a :: Type -> Type) b where
- runWriterLocal :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, Monoid w) => Eff (Writer w ': es) a -> Eff es (a, w)
- execWriterLocal :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, Monoid w) => Eff (Writer w ': es) a -> Eff es w
- runWriterShared :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, Monoid w) => Eff (Writer w ': es) a -> Eff es (a, w)
- execWriterShared :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, Monoid w) => Eff (Writer w ': es) a -> Eff es w
- tell :: forall w (es :: [Effect]). (HasCallStack, Writer w :> es) => w -> Eff es ()
- listen :: forall w (es :: [Effect]) a. (HasCallStack, Writer w :> es) => Eff es a -> Eff es (a, w)
- listens :: forall w (es :: [Effect]) b a. (HasCallStack, Writer w :> es) => (w -> b) -> Eff es a -> Eff es (a, b)
Effect
data Writer w (a :: Type -> Type) b where Source #
Provide access to a write only value of type w
.
Constructors
Tell :: forall w (a :: Type -> Type). w -> Writer w a () | |
Listen :: forall (a :: Type -> Type) a1 w. a a1 -> Writer w a (a1, w) |
Instances
type DispatchOf (Writer w) Source # | |
Defined in Effectful.Internal.MTL |
Handlers
Local
runWriterLocal :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, 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 :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, 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 :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, 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 :: forall w (es :: [(Type -> Type) -> Type -> Type]) a. (HasCallStack, 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 :: forall w (es :: [Effect]). (HasCallStack, Writer w :> es) => w -> Eff es () Source #
Append the given output to the overall output of the Writer
.
listen :: forall w (es :: [Effect]) a. (HasCallStack, Writer w :> es) => Eff es a -> Eff es (a, w) Source #
Execute an action and append its output to the overall output of the
Writer
.