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

Data.Effect.Provider

Description

This module provides the Provider effect, like Effectful.Provider in the effectful package.

Synopsis

Documentation

data Scope t i b :: Effect where Source #

An effect to introduce a new local scope that provides effect context b s.

Constructors

Scope :: forall s t i a f b. i s -> ((forall x. f x -> b s x) -> b s a) -> Scope t i b f (t s a)

Introduces a new local scope that provides an effect context b s parameterized by type i s and with results wrapped in t s.

Instances

Instances details
HFunctor (Scope t i b) Source # 
Instance details

Defined in Data.Effect.Provider

Methods

hfmap :: (forall x. f x -> g x) -> Scope t i b f a -> Scope t i b g a #

type LabelOf (Scope t i b) Source # 
Instance details

Defined in Data.Effect.Provider

type LabelOf (Scope t i b) = ScopeLabel t i
type OrderOf (Scope t i b) Source # 
Instance details

Defined in Data.Effect.Provider

type OrderOf (Scope t i b) = 'HigherOrder

scope'_ :: forall {k :: Type} (s :: k) (t :: k -> Type -> Type) (i :: k -> Type) (a :: Type) (b :: k -> Type -> Type) f es ff c. (Free c ff, f ~ Eff ff es, In (Scope t i b) es) => i s -> ((forall (x :: Type). f x -> b s x) -> b s a) -> f (t s a) Source #

Introduces a new local scope that provides an effect context b s parameterized by type i s and with results wrapped in t s.

scope'' :: forall tag {k :: Type} (s :: k) (t :: k -> Type -> Type) (i :: k -> Type) (a :: Type) (b :: k -> Type -> Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag (Scope t i b)) es) => i s -> ((forall (x :: Type). f x -> b s x) -> b s a) -> f (t s a) Source #

Introduces a new local scope that provides an effect context b s parameterized by type i s and with results wrapped in t s.

scope' :: forall key {k :: Type} (s :: k) (t :: k -> Type -> Type) (i :: k -> Type) (a :: Type) (b :: k -> Type -> Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key (Scope t i b) es) => i s -> ((forall (x :: Type). f x -> b s x) -> b s a) -> f (t s a) Source #

Introduces a new local scope that provides an effect context b s parameterized by type i s and with results wrapped in t s.

scope :: forall {k :: Type} (s :: k) (t :: k -> Type -> Type) (i :: k -> Type) (a :: Type) (b :: k -> Type -> Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Scope t i b) es) => i s -> ((forall (x :: Type). f x -> b s x) -> b s a) -> f (t s a) Source #

Introduces a new local scope that provides an effect context b s parameterized by type i s and with results wrapped in t s.

data ScopeLabel (t :: k -> Type -> Type) (i :: k -> Type) Source #

A type-level label to uniquely resolve the effect context carrier b from t and i.

newtype Const1 f x (a :: Type) Source #

Constructors

Const1 

Fields

type Scoped ff t i es r = Scope t i (ScopeC ff t i es r) Source #

An effect to introduce a new local scope that provides the scope-parametrized effect es.

newtype ScopeC ff t i fs r s a Source #

Constructors

ScopeC 

Fields

type Scoped_ ff t i es r = Scope t i (Const1 (ScopeC_ ff t i es r)) Source #

An effect to introduce a new local scope that provides the effect es.

newtype ScopeC_ ff t i es r a Source #

Constructors

ScopeC_ 

Fields

type Provider ff t i e es = Scoped_ ff (Const1 t) (Const i :: () -> Type) e es Source #

runScoped :: forall t i a es r ff c. (KnownLength es, Free c ff) => (forall s x. i s -> Eff ff (Each es s ++ (Scoped ff t i es r ': r)) x -> Eff ff (Scoped ff t i es r ': r) (t s x)) -> Eff ff (Scoped ff t i es r ': r) a -> Eff ff r a Source #

scoped :: forall t i s a es' es r ff c. (Scoped ff t i es r :> es', Free c ff) => i s -> ((Eff ff es' ~> Eff ff (Each es s ++ (Scoped ff t i es r ': r))) -> Eff ff (Each es s ++ (Scoped ff t i es r ': r)) a) -> Eff ff es' (t s a) Source #

runScoped_ :: forall t i a es r ff c. (KnownLength es, Free c ff) => (forall p x. i p -> Eff ff (es ++ (Scoped_ ff t i es r ': r)) x -> Eff ff (Scoped_ ff t i es r ': r) (t p x)) -> Eff ff (Scoped_ ff t i es r ': r) a -> Eff ff r a Source #

scoped_ :: forall t i s a es' es r ff c. (Scoped_ ff t i es r :> es', Free c ff) => i s -> ((Eff ff es' ~> Eff ff (es ++ (Scoped_ ff t i es r ': r))) -> Eff ff (es ++ (Scoped_ ff t i es r ': r)) a) -> Eff ff es' (t s a) Source #

runProvider :: forall t i a es r ff c. (forall es'. Functor (Eff ff es'), KnownLength es, Free c ff) => (forall x. i -> Eff ff (es ++ (Provider ff t i es r ': r)) x -> Eff ff (Provider ff t i es r ': r) (t x)) -> Eff ff (Provider ff t i es r ': r) a -> Eff ff r a Source #

provide :: forall t i a es' es r ff c. (Provider ff t i es r :> es', forall es''. Functor (Eff ff es''), Free c ff) => i -> ((Eff ff es' ~> Eff ff (es ++ (Provider ff t i es r ': r))) -> Eff ff (es ++ (Provider ff t i es r ': r)) a) -> Eff ff es' (t a) Source #

runProvider_ :: forall i a es r ff c. (forall es'. Functor (Eff ff es'), KnownLength es, Free c ff) => (forall x. i -> Eff ff (es ++ (Provider ff Identity i es r ': r)) x -> Eff ff (Provider ff Identity i es r ': r) x) -> Eff ff (Provider ff Identity i es r ': r) a -> Eff ff r a Source #

provide_ :: forall i a es' es r ff c. (Provider ff Identity i es r :> es', forall es''. Functor (Eff ff es''), Free c ff) => i -> ((Eff ff es' ~> Eff ff (es ++ (Provider ff Identity i es r ': r))) -> Eff ff (es ++ (Provider ff Identity i es r ': r)) a) -> Eff ff es' a Source #

runProvider__ :: forall a es r ff c. (forall es'. Functor (Eff ff es'), KnownLength es, Free c ff) => (forall x. Eff ff (es ++ (Provider ff Identity () es r ': r)) x -> Eff ff (Provider ff Identity () es r ': r) x) -> Eff ff (Provider ff Identity () es r ': r) a -> Eff ff r a Source #

provide__ :: forall a es' es r ff c. (Provider ff Identity () es r :> es', forall es''. Functor (Eff ff es''), Free c ff) => ((Eff ff es' ~> Eff ff (es ++ (Provider ff Identity () es r ': r))) -> Eff ff (es ++ (Provider ff Identity () es r ': r)) a) -> Eff ff es' a Source #