Copyright | (c) 2023 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Accum
Description
Documentation
data Accum w (a :: Type -> Type) b where Source #
Constructors
Add :: forall w (a :: Type -> Type). w -> Accum w a () | |
Look :: forall w (a :: Type -> Type). Accum w a w |
Instances
FirstOrder (Accum w) Source # | |
Defined in Data.Effect.Accum | |
PolyHFunctor (Accum w) Source # | |
Defined in Data.Effect.Accum | |
HFunctor (Accum w) Source # | |
Defined in Data.Effect.Accum | |
type FormOf (Accum w) Source # | |
Defined in Data.Effect.Accum | |
type LabelOf (Accum w) Source # | |
Defined in Data.Effect.Accum | |
type OrderOf (Accum w) Source # | |
Defined in Data.Effect.Accum |
data AccumLabel Source #
add :: forall w f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Accum w :> es) => w -> f () Source #
add' :: forall {k} (key :: k) w f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Accum w) es) => w -> f () Source #
add'' :: forall {k} (tag :: k) w f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Accum w) :> es) => w -> f () Source #
add'_ :: forall w f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Accum w) es) => w -> f () Source #
look :: forall w f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Accum w :> es) => f w Source #
look' :: forall {k} (key :: k) w f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Accum w) es) => f w Source #