Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- data State s :: Effect
- runState :: s -> Eff (State s : es) a -> Eff es (a, s)
- evalState :: s -> Eff (State s : es) a -> Eff es a
- execState :: s -> Eff (State s : es) a -> Eff es s
- runStateMVar :: MVar s -> Eff (State s : es) a -> Eff es (a, s)
- evalStateMVar :: MVar s -> Eff (State s : es) a -> Eff es a
- execStateMVar :: MVar s -> Eff (State s : es) a -> Eff es s
- get :: State s :> es => Eff es s
- gets :: State s :> es => (s -> a) -> Eff es a
- put :: State s :> es => s -> Eff es ()
- state :: State s :> es => (s -> (a, s)) -> Eff es a
- modify :: State s :> es => (s -> s) -> Eff es ()
- stateM :: State s :> es => (s -> Eff es (a, s)) -> Eff es a
- modifyM :: State s :> es => (s -> Eff es s) -> Eff es ()
Effect
data State s :: Effect Source #
Provide access to a strict (WHNF), shared, mutable value of type s
.
Instances
type DispatchOf (State s) Source # | |
Defined in Effectful.State.Static.Shared | |
newtype StaticRep (State s) Source # | |
Defined in Effectful.State.Static.Shared |
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.
Operations
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.