data-effects-0.4.2.0: A basic framework for effect systems based on effects represented by GADTs.
Safe HaskellNone
LanguageGHC2021

Data.Effect.Select

Documentation

data Select r (a :: Type -> Type) b where Source #

Constructors

Select :: forall b r (a :: Type -> Type). ((b -> r) -> b) -> Select r a b 

Instances

Instances details
FirstOrder (Select r) Source # 
Instance details

Defined in Data.Effect.Select

PolyHFunctor (Select r) Source # 
Instance details

Defined in Data.Effect.Select

HFunctor (Select r) Source # 
Instance details

Defined in Data.Effect.Select

Methods

hfmap :: (forall x. f x -> g x) -> Select r f a -> Select r g a #

type FormOf (Select r) Source # 
Instance details

Defined in Data.Effect.Select

type LabelOf (Select r) Source # 
Instance details

Defined in Data.Effect.Select

type OrderOf (Select r) Source # 
Instance details

Defined in Data.Effect.Select

select :: forall a r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Select r :> es) => ((a -> r) -> a) -> f a Source #

select' :: forall {k} (key :: k) a r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Select r) es) => ((a -> r) -> a) -> f a Source #

select'' :: forall {k} (tag :: k) a r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Select r) :> es) => ((a -> r) -> a) -> f a Source #

select'_ :: forall a r f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Select r) es) => ((a -> r) -> a) -> f a Source #