effectful-core-1.2.0.0: An easy to use, performant extensible effects library.
Safe HaskellNone
LanguageHaskell2010

Effectful.State.Static.Local

Description

Support for access to a mutable value of a particular type.

The value is thread local. If you want it to be shared between threads, use Effectful.State.Static.Shared.

Note: unlike the StateT monad transformer from the transformers library, the State effect doesn't discard state updates when an exception is received:

>>> import qualified Control.Monad.Trans.State.Strict as S
>>> :{
  (`S.execStateT` "Hi") . handle (\(_::ErrorCall) -> pure ()) $ do
    S.modify (++ " there!")
    error "oops"
:}
"Hi"
>>> :{
  runEff . execState "Hi" . handle (\(_::ErrorCall) -> pure ()) $ do
    modify (++ " there!")
    error "oops"
:}
"Hi there!"
Synopsis

Effect

data State s :: Effect Source #

Provide access to a strict (WHNF), thread local, mutable value of type s.

Instances

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

Defined in Effectful.State.Static.Local

newtype StaticRep (State s) Source # 
Instance details

Defined in Effectful.State.Static.Local

newtype StaticRep (State s) = State s

Handlers

runState Source #

Arguments

:: s

The initial state.

-> Eff (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.

evalState Source #

Arguments

:: s

The initial state.

-> Eff (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.

execState Source #

Arguments

:: s

The initial state.

-> Eff (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.

Operations

get :: State s :> es => Eff es s Source #

Fetch the current value of the state.

gets Source #

Arguments

:: State s :> es 
=> (s -> a)

The function to apply to the state.

-> Eff es a 

Get a function of the current state.

gets f ≡ f <$> get

put :: State s :> es => s -> Eff es () Source #

Set the current state to the given value.

state Source #

Arguments

:: State s :> es 
=> (s -> (a, s))

The function to modify the state.

-> Eff es a 

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

modify Source #

Arguments

:: State s :> es 
=> (s -> s)

The function to modify the state.

-> Eff es () 

Apply the function to the current state.

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

stateM Source #

Arguments

:: State s :> es 
=> (s -> Eff es (a, s))

The function to modify the state.

-> Eff es a 

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

modifyM Source #

Arguments

:: State s :> es 
=> (s -> Eff es s)

The monadic function to modify the state.

-> Eff es () 

Apply the monadic function to the current state.

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