data-effects-0.4.2.0: 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 HaskellNone
LanguageGHC2021

Data.Effect.Reader

Description

Effects that can be used to hold environmental values in the context. Environmental values are immutable and do not change across procedures, but you can modify the value within a local scope using the local operation.

Synopsis

Documentation

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

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

runReader :: forall r (es :: [(Type -> Type) -> Type -> Type]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (forall (es' :: [Effect]). Applicative (Eff ff es'), Free c ff) => r -> Eff ff (Local r ': (Ask r ': es)) a -> Eff ff es a Source #

Interpret the Ask/Local effects.

asks :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Ask r :> es, Functor (Eff ff es), Free c ff) => (r -> a) -> Eff ff es a Source #

Obtains a value from the environment and returns it transformed by the given function.

runAsk :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), Free c ff) => r -> Eff ff (Ask r ': es) a -> Eff ff es a Source #

Interpret the Ask effect.

runLocal :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), In (Ask r) es, Free c ff) => Eff ff (Local r ': es) a -> Eff ff es a Source #

Interpret the Local effect.

handleLocal :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), In (Ask r) es, Free c ff) => Local r ~~> Eff ff es Source #

A handler for the Local effect.

handleLocalFor :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), Free c ff) => Membership (Ask r) es -> Local r ~~> Eff ff es Source #

A handler for the Local effect.

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

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

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

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

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

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

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

An effect that holds a value of type r in the context (environment).

Constructors

Ask :: forall r (a :: Type -> Type). Ask r a r

Obtain a value from the environment.

Instances

Instances details
FirstOrder (Ask r) 
Instance details

Defined in Data.Effect

PolyHFunctor (Ask r) 
Instance details

Defined in Data.Effect

HFunctor (Ask r) 
Instance details

Defined in Data.Effect

Methods

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

type FormOf (Ask r) 
Instance details

Defined in Data.Effect

type FormOf (Ask r) = 'Polynomial
type LabelOf (Ask r) 
Instance details

Defined in Data.Effect

type LabelOf (Ask r) = AskLabel
type OrderOf (Ask r) 
Instance details

Defined in Data.Effect

type OrderOf (Ask r) = 'FirstOrder

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

An effect that locally modifies the value held in the environment.

Constructors

Local

Locally modifies the value held in the environment.

Fields

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

    A function that transforms the original value to the modified value.

  • -> a b

    The local scope where the modification is applied.

  • -> Local r a b
     

Instances

Instances details
PolyHFunctor (Local r) 
Instance details

Defined in Data.Effect

HFunctor (Local r) 
Instance details

Defined in Data.Effect

Methods

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

type FormOf (Local r) 
Instance details

Defined in Data.Effect

type FormOf (Local r) = 'Polynomial
type LabelOf (Local r) 
Instance details

Defined in Data.Effect

type OrderOf (Local r) 
Instance details

Defined in Data.Effect