Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The dynamically dispatched variant of the State
effect.
Note: unless you plan to change interpretations at runtime, it's recommended to use one of the statically dispatched variants, i.e. Effectful.State.Static.Local or Effectful.State.Static.Shared.
Synopsis
- data State s :: Effect where
- runStateLocal :: s -> Eff (State s : es) a -> Eff es (a, s)
- evalStateLocal :: s -> Eff (State s : es) a -> Eff es a
- execStateLocal :: s -> Eff (State s : es) a -> Eff es s
- runStateShared :: s -> Eff (State s : es) a -> Eff es (a, s)
- evalStateShared :: s -> Eff (State s : es) a -> Eff es a
- execStateShared :: s -> Eff (State s : es) a -> Eff es s
- get :: (HasCallStack, State s :> es) => Eff es s
- gets :: (HasCallStack, State s :> es) => (s -> a) -> Eff es a
- put :: (HasCallStack, State s :> es) => s -> Eff es ()
- state :: (HasCallStack, State s :> es) => (s -> (a, s)) -> Eff es a
- modify :: (HasCallStack, State s :> es) => (s -> s) -> Eff es ()
- stateM :: (HasCallStack, State s :> es) => (s -> Eff es (a, s)) -> Eff es a
- modifyM :: (HasCallStack, State s :> es) => (s -> Eff es s) -> Eff es ()
Effect
data State s :: Effect where Source #
Provide access to a mutable value of type s
.
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
type DispatchOf (State s) Source # | |
Defined in Effectful.State.Dynamic |
Handlers
Local
runStateLocal :: 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 (via Effectful.State.Static.Local).
evalStateLocal :: 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 (via Effectful.State.Static.Local).
execStateLocal :: 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 (via Effectful.State.Static.Local).
Shared
runStateShared :: 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 (via Effectful.State.Static.Shared).
evalStateShared :: 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 (via Effectful.State.Static.Shared).
execStateShared :: 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 (via Effectful.State.Static.Shared).
Operations
put :: (HasCallStack, State s :> es) => s -> Eff es () Source #
Set the current state to the given value.
state :: (HasCallStack, State s :> es) => (s -> (a, s)) -> Eff es a Source #
Apply the function to the current state and return a value.