Copyright | (c) 2023 Sayo contributors |
---|---|
License | MPL-2.0 (see the LICENSE file) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Control.Monad.Hefty.Writer
Description
Interpreters for the Writer effects.
Synopsis
- runWriterPost :: forall w (es :: [Effect]) a. (Monoid w, FOEs es) => Eff (WriterH w ': (Tell w ': es)) a -> Eff es (w, a)
- handleTell :: forall w (f :: Type -> Type) (g :: Type -> Type) a. Monoid w => StateHandler w (Tell w) f g (w, a)
- runTell :: forall w (es :: [Effect]) a. (Monoid w, FOEs es) => Eff (Tell w ': es) a -> Eff es (w, a)
- runWriterHPost :: forall w (es :: [Effect]) a. (Monoid w, In (Tell w) es, FOEs es) => Eff (WriterH w ': es) a -> Eff es a
- runWriterPre :: forall w (es :: [Effect]) a. (Monoid w, FOEs es) => Eff (WriterH w ': (Tell w ': es)) a -> Eff es (w, a)
- runWriterHPre :: forall w (es :: [Effect]) a. (Monoid w, In (Tell w) es, FOEs es) => Eff (WriterH w ': es) a -> Eff es a
- intercept :: forall w (es :: [Effect]) a. (In (Tell w) es, Monoid w, FOEs es) => Eff es a -> Eff es (w, a)
- censorPost :: forall w a (es :: [Effect]). (In (Tell w) es, Monoid w, FOEs es) => (w -> w) -> Eff es a -> Eff es a
- confiscate :: forall w (es :: [Effect]) a. (In (Tell w) es, Monoid w, FOEs es) => Eff es a -> Eff es (w, a)
- module Data.Effect.Writer
Documentation
runWriterPost :: forall w (es :: [Effect]) a. (Monoid w, FOEs es) => Eff (WriterH w ': (Tell w ': es)) a -> Eff es (w, a) Source #
Interpret the Writer effects with post-applying censor semantics.
handleTell :: forall w (f :: Type -> Type) (g :: Type -> Type) a. Monoid w => StateHandler w (Tell w) f g (w, a) Source #
A handler function for the Tell
effect.
runTell :: forall w (es :: [Effect]) a. (Monoid w, FOEs es) => Eff (Tell w ': es) a -> Eff es (w, a) Source #
Interpret the Tell
effect.
runWriterHPost :: forall w (es :: [Effect]) a. (Monoid w, In (Tell w) es, FOEs es) => Eff (WriterH w ': es) a -> Eff es a Source #
Interpret the WriterH
effect with post-applying censor semantics.
runWriterPre :: forall w (es :: [Effect]) a. (Monoid w, FOEs es) => Eff (WriterH w ': (Tell w ': es)) a -> Eff es (w, a) Source #
Interpret the Writer effects with pre-applying censor semantics.
runWriterHPre :: forall w (es :: [Effect]) a. (Monoid w, In (Tell w) es, FOEs es) => Eff (WriterH w ': es) a -> Eff es a Source #
Interpret the WriterH
effect with pre-applying censor semantics.
intercept :: forall w (es :: [Effect]) a. (In (Tell w) es, Monoid w, FOEs es) => Eff es a -> Eff es (w, a) Source #
censorPost :: forall w a (es :: [Effect]). (In (Tell w) es, Monoid w, FOEs es) => (w -> w) -> Eff es a -> Eff es a Source #
censor
with post-applying semantics.
confiscate :: forall w (es :: [Effect]) a. (In (Tell w) es, Monoid w, FOEs es) => Eff es a -> Eff es (w, a) Source #
Consumes all the tell
effects from the specified Tell w
slot within the
given action and returns the accumulated monoidal value along with the result.
module Data.Effect.Writer