Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A state effect that allows atomic updates with monadic actions.
Synopsis
- data MState s :: Effect where
- muse :: Member (MState s) r => (s -> Sem r (s, a)) -> Sem r a
- mtrans :: Member (MState s) r => (s -> Sem r s) -> Sem r ()
- mstate :: Member (MState s) r => (s -> (s, a)) -> Sem r a
- mmodify :: Member (MState s) r => (s -> s) -> Sem r ()
- mput :: Member (MState s) r => s -> Sem r ()
- mread :: Member (MState s) r => Sem r s
- mreads :: Member (MState s) r => (s -> a) -> Sem r a
- stateToMState :: Member (MState s) r => InterpreterFor (State s) r
- type ScopedMState s = PScoped s () (MState s)
- withMState :: Member (ScopedMState s) r => s -> InterpreterFor (MState s) r
Documentation
data MState s :: Effect where Source #
A state effect that allows atomic updates with monadic actions.
The constructor muse
is analogous to the usual state
combinator, in that it transforms the state monadically
alongside a return value, but unlike State
and AtomicState
, the callback may be a Sem
.
This is accomplished by locking every call with an MVar
.
For read-only access to the state that doesn't care about currently running updates, the constructor mread
directly
returns the state without consulting the lock.
muse :: Member (MState s) r => (s -> Sem r (s, a)) -> Sem r a Source #
Run a monadic action on the state in a mutually exclusive fashion that additionally returns a value.
mtrans :: Member (MState s) r => (s -> Sem r s) -> Sem r () Source #
Run a monadic action on the state in a mutually exclusive fashion.
mstate :: Member (MState s) r => (s -> (s, a)) -> Sem r a Source #
Apply a pure function to the state that additionally returns a value.
mreads :: Member (MState s) r => (s -> a) -> Sem r a Source #
Obtain the current state, transformed by a pure function.
stateToMState :: Member (MState s) r => InterpreterFor (State s) r Source #
type ScopedMState s = PScoped s () (MState s) Source #
withMState :: Member (ScopedMState s) r => s -> InterpreterFor (MState s) r Source #