Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Lazy state effect
- data State s v where
- get :: Member (State s) r => Eff r s
- put :: Member (State s) r => s -> Eff r ()
- runState' :: s -> Eff (State s ': r) a -> Eff r (a, s)
- runState :: s -> Eff (State s ': r) a -> Eff r (a, s)
- modify :: Member (State s) r => (s -> s) -> Eff r ()
- evalState :: s -> Eff (State s ': r) a -> Eff r a
- execState :: s -> Eff (State s ': r) a -> Eff r s
- data TxState s = TxState
- transactionState :: forall s r a. Member (State s) r => TxState s -> Eff r a -> Eff r a
- runStateR :: s -> Eff (Writer s ': (Reader s ': r)) a -> Eff r (a, s)
Documentation
State, lazy
Initial design: The state request carries with it the state mutator function We can use this request both for mutating and getting the state. But see below for a better design!
data State s v where State :: (s->s) -> State s s
In this old design, we have assumed that the dominant operation is modify. Perhaps this is not wise. Often, the reader is most nominant.
See also below, for decomposing the State into Reader and Writer!
The conventional design of State
get :: Member (State s) r => Eff r s Source #
Return the current value of the state. The signatures are inferred
runState' :: s -> Eff (State s ': r) a -> Eff r (a, s) Source #
Run a state effect. compared to the runState
function, this is
implemented naively and is expected to perform slower.
:: s | Initial state |
-> Eff (State s ': r) a | Effect incorporating State |
-> Eff r (a, s) | Effect containing final state and a return value |
Run a State effect. This variant is a bit optimized compared to
runState'
.
evalState :: s -> Eff (State s ': r) a -> Eff r a Source #
Run a State effect, discarding the final state.
execState :: s -> Eff (State s ': r) a -> Eff r s Source #
Run a State effect and return the final state.
An encapsulated State handler, for transactional semantics The global state is updated only if the transactionState finished successfully