Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data State s :: Effect where
- get :: State s :> es => Eff es s
- put :: State s :> es => s -> Eff es ()
- state :: State s :> es => (s -> (a, s)) -> Eff es a
- gets :: State s :> es => (s -> t) -> Eff es t
- modify :: State s :> es => (s -> s) -> Eff es ()
- runState :: s -> Eff (State s ': es) a -> Eff es (a, s)
- zoom :: State t :> es => Lens' t s -> Eff (State s ': es) ~> Eff es
Effect
data State s :: Effect where Source #
An effect capable of providing a mutable state s
that can be read and written. This roughly corresponds to the
MonadState
typeclass and StateT
monad transformer in the mtl
approach.
Operations
modify :: State s :> es => (s -> s) -> Eff es () Source #
Modify the value of the state via a function.
Interpretations
runState :: s -> Eff (State s ': es) a -> Eff es (a, s) Source #
Run the State
effect.
Caveat: The runState
interpreter is implemented with IORef
s and there is no way to do arbitrary atomic
transactions at all. The state
operation is atomic though and it is implemented with atomicModifyIORefCAS
which
can be faster in contention. For any more complicated cases of atomicity please build your own effect that uses
either MVar
s or TVar
s based on your need.
Unlike mtl
, in cleff
the state will not revert when an error is thrown.
runState
will stop taking care of state operations done on forked threads as soon as the main thread finishes its
computation. Any state operation done before main thread finishes is still taken into account.