effectful-core-2.5.0.0: An easy to use, performant extensible effects library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful.Labeled.State

Description

Convenience functions for the Labeled State effect.

Since: 2.4.0.0

Synopsis

Effect

data State s :: Effect where Source #

Provide access to a mutable value of type s.

Constructors

Get :: State s m s 
Put :: s -> State s m () 
State :: (s -> (a, s)) -> State s m a 
StateM :: (s -> m (a, s)) -> State s m a 

Instances

Instances details
type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Dynamic

Handlers

Local

runStateLocal Source #

Arguments

:: forall label s es a. HasCallStack 
=> s

The initial state.

-> Eff (Labeled label (State s) : es) a 
-> Eff es (a, s) 

Run the State effect with the given initial state and return the final value along with the final state (via Effectful.State.Static.Local).

evalStateLocal Source #

Arguments

:: forall label s es a. HasCallStack 
=> s

The initial state.

-> Eff (Labeled label (State s) : es) a 
-> Eff es a 

Run the State effect with the given initial state and return the final value, discarding the final state (via Effectful.State.Static.Local).

execStateLocal Source #

Arguments

:: forall label s es a. HasCallStack 
=> s

The initial state.

-> Eff (Labeled label (State s) : es) a 
-> Eff es s 

Run the State effect with the given initial state and return the final state, discarding the final value (via Effectful.State.Static.Local).

Shared

runStateShared Source #

Arguments

:: forall label s es a. HasCallStack 
=> s

The initial state.

-> Eff (Labeled label (State s) : es) a 
-> Eff es (a, s) 

Run the State effect with the given initial state and return the final value along with the final state (via Effectful.State.Static.Shared).

evalStateShared Source #

Arguments

:: forall label s es a. HasCallStack 
=> s

The initial state.

-> Eff (Labeled label (State s) : es) a 
-> Eff es a 

Run the State effect with the given initial state and return the final value, discarding the final state (via Effectful.State.Static.Shared).

execStateShared Source #

Arguments

:: forall label s es a. HasCallStack 
=> s

The initial state.

-> Eff (Labeled label (State s) : es) a 
-> Eff es s 

Run the State effect with the given initial state and return the final state, discarding the final value (via Effectful.State.Static.Shared).

Operations

get :: forall label s es. (HasCallStack, Labeled label (State s) :> es) => Eff es s Source #

Fetch the current value of the state.

gets Source #

Arguments

:: forall label s es a. (HasCallStack, Labeled label (State s) :> es) 
=> (s -> a)

.

-> Eff es a 

Get a function of the current state.

gets f ≡ f <$> get

put Source #

Arguments

:: forall label s es. (HasCallStack, Labeled label (State s) :> es) 
=> s

.

-> Eff es () 

Set the current state to the given value.

state Source #

Arguments

:: forall label s es a. (HasCallStack, Labeled label (State s) :> es) 
=> (s -> (a, s))

.

-> Eff es a 

Apply the function to the current state and return a value.

modify Source #

Arguments

:: forall label s es. (HasCallStack, Labeled label (State s) :> es) 
=> (s -> s)

.

-> Eff es () 

Apply the function to the current state.

modify f ≡ state (\s -> ((), f s))

stateM Source #

Arguments

:: forall label s es a. (HasCallStack, Labeled label (State s) :> es) 
=> (s -> Eff es (a, s))

.

-> Eff es a 

Apply the monadic function to the current state and return a value.

modifyM Source #

Arguments

:: forall label s es. (HasCallStack, Labeled label (State s) :> es) 
=> (s -> Eff es s)

.

-> Eff es () 

Apply the monadic function to the current state.

modifyM f ≡ stateM (\s -> ((), ) <$> f s)