heftia-effects-0.4.0.0: higher-order effects done right
Copyright(c) 2024 Sayo Koyoneda
LicenseMPL-2.0 (see the LICENSE file)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Control.Monad.Hefty.Provider

Description

 

Documentation

type ProviderFix (ctx :: Type -> Type) i (eh :: EffectH) (rh :: [EffectH]) (ef :: EffectF) (rf :: [EffectF]) = Provider ctx i (ProviderBase ctx i eh rh ef rf) Source #

type ProviderFix_ i (eh :: EffectH) (rh :: [EffectH]) (ef :: EffectF) (rf :: [EffectF]) = Provider Identity i (ProviderBase Identity i eh rh ef rf) Source #

newtype ProviderBase (ctx :: Type -> Type) i (eh :: EffectH) (rh :: [EffectH]) (ef :: EffectF) (rf :: [EffectF]) a Source #

Constructors

ProviderBase 

Fields

Instances

Instances details
Applicative (ProviderBase ctx i eh rh ef rf) Source # 
Instance details

Defined in Control.Monad.Hefty.Provider

Methods

pure :: a -> ProviderBase ctx i eh rh ef rf a #

(<*>) :: ProviderBase ctx i eh rh ef rf (a -> b) -> ProviderBase ctx i eh rh ef rf a -> ProviderBase ctx i eh rh ef rf b #

liftA2 :: (a -> b -> c) -> ProviderBase ctx i eh rh ef rf a -> ProviderBase ctx i eh rh ef rf b -> ProviderBase ctx i eh rh ef rf c #

(*>) :: ProviderBase ctx i eh rh ef rf a -> ProviderBase ctx i eh rh ef rf b -> ProviderBase ctx i eh rh ef rf b #

(<*) :: ProviderBase ctx i eh rh ef rf a -> ProviderBase ctx i eh rh ef rf b -> ProviderBase ctx i eh rh ef rf a #

Functor (ProviderBase ctx i eh rh ef rf) Source # 
Instance details

Defined in Control.Monad.Hefty.Provider

Methods

fmap :: (a -> b) -> ProviderBase ctx i eh rh ef rf a -> ProviderBase ctx i eh rh ef rf b #

(<$) :: a -> ProviderBase ctx i eh rh ef rf b -> ProviderBase ctx i eh rh ef rf a #

Monad (ProviderBase ctx i eh rh ef rf) Source # 
Instance details

Defined in Control.Monad.Hefty.Provider

Methods

(>>=) :: ProviderBase ctx i eh rh ef rf a -> (a -> ProviderBase ctx i eh rh ef rf b) -> ProviderBase ctx i eh rh ef rf b #

(>>) :: ProviderBase ctx i eh rh ef rf a -> ProviderBase ctx i eh rh ef rf b -> ProviderBase ctx i eh rh ef rf b #

return :: a -> ProviderBase ctx i eh rh ef rf a #

runProvider :: forall ctx i (eh :: EffectH) (rh :: [EffectH]) (ef :: EffectF) (rf :: [EffectF]). (forall x. i -> Eff (eh ': (ProviderFix ctx i eh rh ef rf ': rh)) (ef ': rf) x -> Eff (ProviderFix ctx i eh rh ef rf ': rh) rf (ctx x)) -> Eff (ProviderFix ctx i eh rh ef rf ': rh) rf ~> Eff rh rf Source #

runProvider_ :: forall i (eh :: EffectH) (rh :: [EffectH]) (ef :: EffectF) (rf :: [EffectF]). (i -> Eff (eh ': (ProviderFix_ i eh rh ef rf ': rh)) (ef ': rf) ~> Eff (ProviderFix_ i eh rh ef rf ': rh) rf) -> Eff (ProviderFix_ i eh rh ef rf ': rh) rf ~> Eff rh rf Source #

provide :: forall {k} (tag :: k) ctx i (eh :: [EffectH]) (ef :: [EffectF]) a (sh :: EffectH) (bh :: [EffectH]) (sf :: EffectF) (bf :: [EffectF]). (MemberHBy (ProviderKey ctx i) (Provider' ctx i (ProviderBase ctx i sh bh sf bf)) eh, HFunctor sh) => i -> ((Eff eh ef ~> Eff ((sh ## tag) ': (ProviderFix ctx i sh bh sf bf ': bh)) ((sf # tag) ': bf)) -> Eff ((sh ## tag) ': (ProviderFix ctx i sh bh sf bf ': bh)) ((sf # tag) ': bf) a) -> Eff eh ef (ctx a) Source #

provide_ :: forall {k} (tag :: k) i (eh :: [EffectH]) (ef :: [EffectF]) a (sh :: EffectH) (bh :: [EffectH]) (sf :: EffectF) (bf :: [EffectF]). (MemberHBy (ProviderKey Identity i) (Provider' Identity i (ProviderBase Identity i sh bh sf bf)) eh, HFunctor sh) => i -> ((Eff eh ef ~> Eff ((sh ## tag) ': (ProviderFix_ i sh bh sf bf ': bh)) ((sf # tag) ': bf)) -> Eff ((sh ## tag) ': (ProviderFix_ i sh bh sf bf ': bh)) ((sf # tag) ': bf) a) -> Eff eh ef a Source #