Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data State s :: Effect where
- runStateLocal :: forall label s es a. HasCallStack => s -> Eff (Labeled label (State s) : es) a -> Eff es (a, s)
- evalStateLocal :: forall label s es a. HasCallStack => s -> Eff (Labeled label (State s) : es) a -> Eff es a
- execStateLocal :: forall label s es a. HasCallStack => s -> Eff (Labeled label (State s) : es) a -> Eff es s
- runStateShared :: forall label s es a. HasCallStack => s -> Eff (Labeled label (State s) : es) a -> Eff es (a, s)
- evalStateShared :: forall label s es a. HasCallStack => s -> Eff (Labeled label (State s) : es) a -> Eff es a
- execStateShared :: forall label s es a. HasCallStack => s -> Eff (Labeled label (State s) : es) a -> Eff es s
- get :: forall label s es. (HasCallStack, Labeled label (State s) :> es) => Eff es s
- gets :: forall label s es a. (HasCallStack, Labeled label (State s) :> es) => (s -> a) -> Eff es a
- put :: forall label s es. (HasCallStack, Labeled label (State s) :> es) => s -> Eff es ()
- state :: forall label s es a. (HasCallStack, Labeled label (State s) :> es) => (s -> (a, s)) -> Eff es a
- modify :: forall label s es. (HasCallStack, Labeled label (State s) :> es) => (s -> s) -> Eff es ()
- stateM :: forall label s es a. (HasCallStack, Labeled label (State s) :> es) => (s -> Eff es (a, s)) -> Eff es a
- modifyM :: forall label s es. (HasCallStack, Labeled label (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
:: forall label s es a. HasCallStack | |
=> s | The initial state. |
-> Eff (Labeled label (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 (via Effectful.State.Static.Local).
:: forall label s es a. HasCallStack | |
=> s | The initial state. |
-> Eff (Labeled label (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 (via Effectful.State.Static.Local).
:: forall label s es a. HasCallStack | |
=> s | The initial state. |
-> Eff (Labeled label (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 (via Effectful.State.Static.Local).
Shared
:: forall label s es a. HasCallStack | |
=> s | The initial state. |
-> Eff (Labeled label (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 (via Effectful.State.Static.Shared).
:: forall label s es a. HasCallStack | |
=> s | The initial state. |
-> Eff (Labeled label (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 (via Effectful.State.Static.Shared).
:: forall label s es a. HasCallStack | |
=> s | The initial state. |
-> Eff (Labeled label (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 (via Effectful.State.Static.Shared).
Operations
get :: forall label s es. (HasCallStack, Labeled label (State s) :> es) => Eff es s Source #
Fetch the current value of the state.
:: forall label s es a. (HasCallStack, Labeled label (State s) :> es) | |
=> (s -> a) | . |
-> Eff es a |
:: forall label s es. (HasCallStack, Labeled label (State s) :> es) | |
=> s | . |
-> Eff es () |
Set the current state to the given value.
:: forall label s es a. (HasCallStack, Labeled label (State s) :> es) | |
=> (s -> (a, s)) | . |
-> Eff es a |
Apply the function to the current state and return a value.
:: forall label s es. (HasCallStack, Labeled label (State s) :> es) | |
=> (s -> s) | . |
-> Eff es () |