Copyright | (c) 2023-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- data Ask r (a :: Type -> Type) b where
- data Local r (a :: Type -> Type) b where
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 #
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).
Instances
FirstOrder (Ask r) | |
Defined in Data.Effect | |
PolyHFunctor (Ask r) | |
Defined in Data.Effect | |
HFunctor (Ask r) | |
Defined in Data.Effect | |
type FormOf (Ask r) | |
Defined in Data.Effect | |
type LabelOf (Ask r) | |
Defined in Data.Effect | |
type OrderOf (Ask r) | |
Defined in Data.Effect |
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. |
Instances
PolyHFunctor (Local r) | |
Defined in Data.Effect | |
HFunctor (Local r) | |
Defined in Data.Effect | |
type FormOf (Local r) | |
Defined in Data.Effect | |
type LabelOf (Local r) | |
Defined in Data.Effect | |
type OrderOf (Local r) | |
Defined in Data.Effect |