Safe Haskell | None |
---|---|
Language | Haskell2010 |
Effectful.Labeled.State
Synopsis
- data State s (a :: Type -> Type) b where
- runStateLocal :: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (Labeled label (State s) ': es) a -> Eff es (a, s)
- evalStateLocal :: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (Labeled label (State s) ': es) a -> Eff es a
- execStateLocal :: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (Labeled label (State s) ': es) a -> Eff es s
- runStateShared :: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (Labeled label (State s) ': es) a -> Eff es (a, s)
- evalStateShared :: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (Labeled label (State s) ': es) a -> Eff es a
- execStateShared :: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (Labeled label (State s) ': es) a -> Eff es s
- get :: forall {k} (label :: k) s (es :: [Effect]). (HasCallStack, Labeled label (State s) :> es) => Eff es s
- gets :: forall {k} (label :: k) s (es :: [Effect]) a. (HasCallStack, Labeled label (State s) :> es) => (s -> a) -> Eff es a
- put :: forall {k} (label :: k) s (es :: [Effect]). (HasCallStack, Labeled label (State s) :> es) => s -> Eff es ()
- state :: forall {k} (label :: k) s (es :: [Effect]) a. (HasCallStack, Labeled label (State s) :> es) => (s -> (a, s)) -> Eff es a
- modify :: forall {k} (label :: k) s (es :: [Effect]). (HasCallStack, Labeled label (State s) :> es) => (s -> s) -> Eff es ()
- stateM :: forall {k} (label :: k) s (es :: [Effect]) a. (HasCallStack, Labeled label (State s) :> es) => (s -> Eff es (a, s)) -> Eff es a
- modifyM :: forall {k} (label :: k) s (es :: [Effect]). (HasCallStack, Labeled label (State s) :> es) => (s -> Eff es s) -> Eff es ()
Effect
data State s (a :: Type -> Type) b where Source #
Provide access to a mutable value of type s
.
Constructors
Get :: forall s (a :: Type -> Type). State s a s | |
Put :: forall s (a :: Type -> Type). s -> State s a () | |
State :: forall s b (a :: Type -> Type). (s -> (b, s)) -> State s a b | |
StateM :: forall s (a :: Type -> Type) b. (s -> a (b, s)) -> State s a b |
Instances
type DispatchOf (State s) Source # | |
Defined in Effectful.State.Dynamic |
Handlers
Local
Arguments
:: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) 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).
Arguments
:: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) 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).
Arguments
:: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) 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
Arguments
:: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) 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).
Arguments
:: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) 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).
Arguments
:: forall {k} (label :: k) s (es :: [(Type -> Type) -> Type -> Type]) 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 {k} (label :: k) s (es :: [Effect]). (HasCallStack, Labeled label (State s) :> es) => Eff es s Source #
Fetch the current value of the state.
Arguments
:: forall {k} (label :: k) s (es :: [Effect]). (HasCallStack, Labeled label (State s) :> es) | |
=> s | . |
-> Eff es () |
Set the current state to the given value.
Arguments
:: forall {k} (label :: k) s (es :: [Effect]) a. (HasCallStack, Labeled label (State s) :> es) | |
=> (s -> (a, s)) | . |
-> Eff es a |
Apply the function to the current state and return a value.