data-effects-0.4.2.0: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2023 Sayo contributors
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

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

Instances details
FirstOrder (Accum w) Source # 
Instance details

Defined in Data.Effect.Accum

PolyHFunctor (Accum w) Source # 
Instance details

Defined in Data.Effect.Accum

HFunctor (Accum w) Source # 
Instance details

Defined in Data.Effect.Accum

Methods

hfmap :: (forall x. f x -> g x) -> Accum w f a -> Accum w g a #

type FormOf (Accum w) Source # 
Instance details

Defined in Data.Effect.Accum

type FormOf (Accum w) = 'Polynomial
type LabelOf (Accum w) Source # 
Instance details

Defined in Data.Effect.Accum

type OrderOf (Accum w) Source # 
Instance details

Defined in Data.Effect.Accum

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 #

look'' :: 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) => f w Source #

look'_ :: 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) => f w Source #