Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- 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
- 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), thread local, mutable value of type s
.
Instances
type DispatchOf (State s) Source # | |
Defined in Effectful.State.Static.Local | |
newtype StaticRep (State s) Source # | |
Defined in Effectful.State.Static.Local |
Handlers
Run the State
effect with the given initial state and return the final
value along with the final state.
Run the State
effect with the given initial state and return the final
value, discarding the final state.
Run the State
effect with the given initial state and return the final
state, discarding the final value.
Operations
Apply the function to the current state and return a value.
Apply the monadic function to the current state and return a value.