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

Effectful.State.Static.Shared

Description

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

The value is shared between multiple threads. If you want each thead to manage its own version of the value, use Effectful.State.Static.Local.

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), shared, mutable value of type s.

Instances

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

Defined in Effectful.State.Static.Shared

newtype StaticRep (State s) Source # 
Instance details

Defined in Effectful.State.Static.Shared

newtype StaticRep (State s) = State (MVar s)

Handlers

runState :: s -> Eff (State s ': es) a -> Eff es (a, s) Source #

Run the State effect with the given initial state and return the final value along with the final state.

evalState :: s -> Eff (State s ': es) a -> Eff es a Source #

Run the State effect with the given initial state and return the final value, discarding the final state.

execState :: s -> Eff (State s ': es) a -> Eff es s Source #

Run the State effect with the given initial state and return the final state, discarding the final value.

runStateMVar :: MVar s -> Eff (State s ': es) a -> Eff es (a, s) Source #

Run the State effect with the given initial state MVar and return the final value along with the final state.

evalStateMVar :: MVar s -> Eff (State s ': es) a -> Eff es a Source #

Run the State effect with the given initial state MVar and return the final value, discarding the final state.

execStateMVar :: MVar s -> Eff (State s ': es) a -> Eff es s Source #

Run the State effect with the given initial state MVar 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 :: State s :> es => (s -> a) -> Eff es a Source #

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 :: State s :> es => (s -> (a, s)) -> Eff es a Source #

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

Note: this function gets an exclusive access to the state for its duration.

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

Apply the function to the current state.

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

Note: this function gets an exclusive access to the state for its duration.

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

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

Note: this function gets an exclusive access to the state for its duration.

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

Apply the monadic function to the current state.

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

Note: this function gets an exclusive access to the state for its duration.