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.State
Description
Effects for holding mutable state values in the context.
Synopsis
- get :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, State s :> es) => a s
- put :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, State s :> es) => s -> a ()
- gets :: forall s (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (State s :> es, Functor (Eff ff es), Free c ff) => (s -> a) -> Eff ff es a
- modify :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (State s :> es, Monad (Eff ff es), Free c ff) => (s -> s) -> Eff ff es ()
- runStateIORef :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es (s, a)
- evalStateIORef :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es a
- execStateIORef :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es s
- localToState :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In (State r) es, Monad (Eff ff es), Free c ff) => Eff ff (Local r ': es) a -> Eff ff es a
- get'_ :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (State s) es) => a s
- put'_ :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (State s) es) => s -> a ()
- askToGet :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In (State r) es, Free c ff) => Eff ff (Ask r ': es) a -> Eff ff es a
- get' :: forall {k} (key :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (State s) es) => a s
- get'' :: forall {k} (tag :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (State s) :> es) => a s
- put' :: forall {k} (key :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (State s) es) => s -> a ()
- put'' :: forall {k} (tag :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (State s) :> es) => s -> a ()
- data State s (a :: Type -> Type) b where
Documentation
get :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, State s :> es) => a s Source #
put :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, State s :> es) => s -> a () Source #
gets :: forall s (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (State s :> es, Functor (Eff ff es), Free c ff) => (s -> a) -> Eff ff es a Source #
Retrieves the current state value from the context and returns the value transformed based on the given function.
modify :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (State s :> es, Monad (Eff ff es), Free c ff) => (s -> s) -> Eff ff es () Source #
Modifies the current state value in the context based on the given function.
runStateIORef :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es (s, a) Source #
evalStateIORef :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es a Source #
execStateIORef :: forall s (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es s Source #
localToState :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In (State r) es, Monad (Eff ff es), Free c ff) => Eff ff (Local r ': es) a -> Eff ff es a Source #
get'_ :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (State s) es) => a s Source #
put'_ :: forall s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (State s) es) => s -> a () Source #
askToGet :: forall r (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In (State r) es, Free c ff) => Eff ff (Ask r ': es) a -> Eff ff es a Source #
get' :: forall {k} (key :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (State s) es) => a s Source #
get'' :: forall {k} (tag :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (State s) :> es) => a s Source #
put' :: forall {k} (key :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (State s) es) => s -> a () Source #
put'' :: forall {k} (tag :: k) s a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (State s) :> es) => s -> a () Source #
data State s (a :: Type -> Type) b where #
An effect for holding mutable state values in the context.
Constructors
Get :: forall s (a :: Type -> Type). State s a s | Retrieves the current state value from the context. |
Put :: forall s (a :: Type -> Type). s -> State s a () | Overwrites the state value in the context. |
Instances
FirstOrder (State s) | |
Defined in Data.Effect | |
PolyHFunctor (State s) | |
Defined in Data.Effect | |
HFunctor (State s) | |
Defined in Data.Effect | |
type FormOf (State s) | |
Defined in Data.Effect | |
type LabelOf (State s) | |
Defined in Data.Effect | |
type OrderOf (State s) | |
Defined in Data.Effect |