Copyright | (c) 2023-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Writer
Description
Effects that can accumulate values monoidally in a context.
Synopsis
- tell :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tell w :> es) => w -> a ()
- listen :: forall a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, WriterH w :> es) => a a1 -> a (w, a1)
- censor :: forall w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, WriterH w :> es) => (w -> w) -> a b -> a b
- censorPre :: forall w (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In (Tell w) es, Free c ff) => (w -> w) -> Eff ff es a -> Eff ff es a
- tell'_ :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (Tell w) es) => w -> a ()
- tell' :: forall {k} (key :: k) w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (Tell w) es) => w -> a ()
- tell'' :: forall {k} (tag :: k) w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (Tell w) :> es) => w -> a ()
- listen' :: forall {k} (key :: k) a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (WriterH w) es) => a a1 -> a (w, a1)
- listen'' :: forall {k} (tag :: k) a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (WriterH w) :> es) => a a1 -> a (w, a1)
- listen'_ :: forall a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (WriterH w) es) => a a1 -> a (w, a1)
- censor' :: forall {k} (key :: k) w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (WriterH w) es) => (w -> w) -> a b -> a b
- censor'' :: forall {k} (tag :: k) w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (WriterH w) :> es) => (w -> w) -> a b -> a b
- censor'_ :: forall w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (WriterH w) es) => (w -> w) -> a b -> a b
- data Tell w (a :: Type -> Type) b where
- data WriterH w (a :: Type -> Type) b where
- pass :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Tell w :> es, WriterH w :> es, Monad (Eff ff es), Free c ff) => Eff ff es (w -> w, a) -> Eff ff es a
Documentation
tell :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tell w :> es) => w -> a () Source #
listen :: forall a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, WriterH w :> es) => a a1 -> a (w, a1) Source #
censor :: forall w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, WriterH w :> es) => (w -> w) -> a b -> a b Source #
censorPre :: forall w (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In (Tell w) es, Free c ff) => (w -> w) -> Eff ff es a -> Eff ff es a Source #
censor
with pre-applying semantics.
tell'_ :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (Tell w) es) => w -> a () Source #
tell' :: forall {k} (key :: k) w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (Tell w) es) => w -> a () Source #
tell'' :: forall {k} (tag :: k) w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (Tell w) :> es) => w -> a () Source #
listen' :: forall {k} (key :: k) a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (WriterH w) es) => a a1 -> a (w, a1) Source #
listen'' :: forall {k} (tag :: k) a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (WriterH w) :> es) => a a1 -> a (w, a1) Source #
listen'_ :: forall a1 w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (WriterH w) es) => a a1 -> a (w, a1) Source #
censor' :: forall {k} (key :: k) w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (WriterH w) es) => (w -> w) -> a b -> a b Source #
censor'' :: forall {k} (tag :: k) w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (WriterH w) :> es) => (w -> w) -> a b -> a b Source #
censor'_ :: forall w b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (WriterH w) es) => (w -> w) -> a b -> a b Source #
data Tell w (a :: Type -> Type) b where #
An effect that can accumulate values monoidally in a context.
Constructors
Tell :: forall w (a :: Type -> Type). w -> Tell w a () | Accumulates new values to the cumulative value held in the context. |
Instances
FirstOrder (Tell w) | |
Defined in Data.Effect | |
PolyHFunctor (Tell w) | |
Defined in Data.Effect | |
HFunctor (Tell w) | |
Defined in Data.Effect | |
type FormOf (Tell w) | |
Defined in Data.Effect | |
type LabelOf (Tell w) | |
Defined in Data.Effect | |
type OrderOf (Tell w) | |
Defined in Data.Effect |
data WriterH w (a :: Type -> Type) b where #
An effect that performs local operations on accumulations in the context on a per-scope basis.
Constructors
Listen | Obtains the accumulated value in the scope and returns it together as a pair. |
Censor | Modifies the accumulation in the scope based on the given function. |
Instances
PolyHFunctor (WriterH w) | |
Defined in Data.Effect | |
HFunctor (WriterH w) | |
Defined in Data.Effect | |
type FormOf (WriterH w) | |
Defined in Data.Effect | |
type LabelOf (WriterH w) | |
Defined in Data.Effect | |
type OrderOf (WriterH w) | |
Defined in Data.Effect |
pass :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Tell w :> es, WriterH w :> es, Monad (Eff ff es), Free c ff) => Eff ff es (w -> w, a) -> Eff ff es a #
For a given scope, uses the function (the first component of the pair returned by that scope) to modify the accumulated value of that scope, and then accumulates the result into the current outer scope.
pass m = do (w, (f, a)) <- listen m tell $ f w pure a