Copyright | (c) 2023 Sayo Koyoneda |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.State
Description
Effects for holding mutable state values in the context.
Synopsis
- data State s a where
- type LState s = LiftFOE (State s)
- pattern LPut :: forall a s f. () => (a ~ (), ()) => s -> LiftFOE (State s) f a
- pattern LGet :: forall a s f. () => (a ~ s, ()) => LiftFOE (State s) f a
- get :: SendFOE (State s) f => f s
- get' :: forall {k} (tag :: k) s f. SendFOE (Tag (State s) tag) f => f s
- get'' :: forall {k} (key :: k) s f. SendFOEBy key (State s) f => f s
- put :: SendFOE (State s) f => s -> f ()
- put' :: forall {k} (tag :: k) s f. SendFOE (Tag (State s) tag) f => s -> f ()
- put'' :: forall {k} (key :: k) s f. SendFOEBy key (State s) f => s -> f ()
- gets :: (State s <: f, Functor f) => (s -> a) -> f a
- modify :: (State s <: m, Monad m) => (s -> s) -> m ()
Documentation
An effect for holding mutable state values in the context.
get' :: forall {k} (tag :: k) s f. SendFOE (Tag (State s) tag) f => f s Source #
Retrieves the current state value from the context.
get'' :: forall {k} (key :: k) s f. SendFOEBy key (State s) f => f s Source #
Retrieves the current state value from the context.
put' :: forall {k} (tag :: k) s f. SendFOE (Tag (State s) tag) f => s -> f () Source #
Overwrites the state value in the context.
put'' :: forall {k} (key :: k) s f. SendFOEBy key (State s) f => s -> f () Source #
Overwrites the state value in the context.