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.State

Description

Effects for holding mutable state values in the context.

Synopsis

Documentation

get :: forall (s :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (State s) es) => a s Source #

put :: forall (s :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (State s) es) => s -> a () Source #

gets :: forall s es a ff c. (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 ff c. (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 ff a c. (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es (s, a) Source #

Interpret the State effect based on an IO-fused semantics using IORef.

evalStateIORef :: forall s es ff a c. (Emb IO :> es, Monad (Eff ff es), Free c ff) => s -> Eff ff (State s ': es) a -> Eff ff es a Source #

Interpret the State effect based on an IO-fused semantics using IORef. Do not include the final state in the return value.

execStateIORef :: forall s es ff a c. (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 ff a c. (State r `In` es, Monad (Eff ff es), Free c ff) => Eff ff (Local r ': es) a -> Eff ff es a Source #

get'_ :: forall (s :: Type) a es ff c. (Free c ff, a ~ Eff ff es, In (State s) es) => a s Source #

put'_ :: forall (s :: Type) a es ff c. (Free c ff, a ~ Eff ff es, In (State s) es) => s -> a () Source #

askToGet :: forall r es ff a c. (State r `In` es, Free c ff) => Eff ff (Ask r ': es) a -> Eff ff es a Source #

get' :: forall key (s :: Type) a es ff c. (Free c ff, a ~ Eff ff es, Has key (State s) es) => a s Source #

get'' :: forall tag (s :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (Tagged tag (State s)) es) => a s Source #

put' :: forall key (s :: Type) a es ff c. (Free c ff, a ~ Eff ff es, Has key (State s) es) => s -> a () Source #

put'' :: forall tag (s :: Type) a es ff c. (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

Instances details
FirstOrder (State s) 
Instance details

Defined in Data.Effect

HFunctor (State s) 
Instance details

Defined in Data.Effect

Methods

hfmap :: (forall x. f x -> g x) -> State s f a -> State s g a #

type LabelOf (State s) 
Instance details

Defined in Data.Effect

type OrderOf (State s) 
Instance details

Defined in Data.Effect