Copyright | (c) 2023 Sayo Koyoneda |
---|---|
License | MPL-2.0 (see the LICENSE file) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Control.Monad.Hefty.State
Description
Interpreter for the State
effect.
Synopsis
- runState :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef (s, a)
- evalState :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef a
- execState :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef s
- evalStateIORef :: forall s (ef :: [EffectF]) (eh :: [EffectH]) a. IO <| ef => s -> Eff eh (State s ': ef) a -> Eff eh ef a
- handleState :: forall s (eh :: [EffectH]) (r :: [EffectF]) ans x. State s x -> s -> (s -> x -> Eff eh r ans) -> Eff eh r ans
- evalStateRec :: forall s (ef :: [Type -> Type]) (eh :: [EffectH]). s -> Eff eh (State s ': ef) ~> Eff eh ef
- runStateIORef :: forall s (ef :: [EffectF]) (eh :: [EffectH]) a. IO <| ef => s -> Eff eh (State s ': ef) a -> Eff eh ef (s, a)
- transactState :: forall s (ef :: [EffectF]). State s <| ef => Eff ('[] :: [EffectH]) ef ~> Eff ('[] :: [EffectH]) ef
- runStateNaive :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef (s, a)
- evalStateNaiveRec :: forall s (ef :: [Type -> Type]) (eh :: [EffectH]). s -> Eff eh (State s ': ef) ~> Eff eh ef
- module Data.Effect.State
Documentation
runState :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef (s, a) Source #
Interpret the State
effect.
evalState :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef a Source #
Interpret the State
effect. Do not include the final state in the return value.
execState :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef s Source #
Interpret the State
effect. Do not include the final result in the return value.
evalStateIORef :: forall s (ef :: [EffectF]) (eh :: [EffectH]) a. IO <| ef => s -> Eff eh (State s ': ef) a -> Eff eh ef a Source #
handleState :: forall s (eh :: [EffectH]) (r :: [EffectF]) ans x. State s x -> s -> (s -> x -> Eff eh r ans) -> Eff eh r ans Source #
A handler function for the State
effect.
evalStateRec :: forall s (ef :: [Type -> Type]) (eh :: [EffectH]). s -> Eff eh (State s ': ef) ~> Eff eh ef Source #
Interpret the State
effect.
Interpretation is performed recursively with respect to the scopes of unelaborated higher-order effects eh
.
Note that the state is reset and does not persist beyond the scopes.
runStateIORef :: forall s (ef :: [EffectF]) (eh :: [EffectH]) a. IO <| ef => s -> Eff eh (State s ': ef) a -> Eff eh ef (s, a) Source #
transactState :: forall s (ef :: [EffectF]). State s <| ef => Eff ('[] :: [EffectH]) ef ~> Eff ('[] :: [EffectH]) ef Source #
Within the given scope, make the state roll back to the beginning of the scope in case of exceptions, etc.
runStateNaive :: forall s (ef :: [Type -> Type]) a. s -> Eff ('[] :: [EffectH]) (State s ': ef) a -> Eff ('[] :: [EffectH]) ef (s, a) Source #
A naive but somewhat slower version of runState
that does not use ad-hoc optimizations.
evalStateNaiveRec :: forall s (ef :: [Type -> Type]) (eh :: [EffectH]). s -> Eff eh (State s ': ef) ~> Eff eh ef Source #
A naive but somewhat slower version of evalStateRec
that does not use ad-hoc optimizations.
module Data.Effect.State