data-effects-0.3.0.1: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2023 Sayo Koyoneda
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Data.Effect.State

Description

Effects for holding mutable state values in the context.

Synopsis

Documentation

data State s a where Source #

An effect for holding mutable state values in the context.

Constructors

Get :: forall s. State s s

Retrieves the current state value from the context.

Put :: forall s. s -> State s ()

Overwrites the state value in the context.

type LState s = LiftFOE (State s) Source #

pattern LPut :: forall a s f. () => (a ~ (), ()) => s -> LiftFOE (State s) f a Source #

pattern LGet :: forall a s f. () => (a ~ s, ()) => LiftFOE (State s) f a Source #

get :: SendFOE (State s) f => f s Source #

Retrieves the current state value from 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 :: SendFOE (State s) f => s -> f () Source #

Overwrites the state value in 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.

gets :: (State s <: f, Functor f) => (s -> a) -> f a Source #

Retrieves the current state value from the context and returns the value transformed based on the given function.

modify :: (State s <: m, Monad m) => (s -> s) -> m () Source #

Modifies the current state value in the context based on the given function.