Copyright | (c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King |
---|---|
License | BSD3 |
Maintainer | Alexis King <lexi.lambda@gmail.com> |
Stability | experimental |
Portability | GHC specific language extensions. |
Safe Haskell | None |
Language | Haskell2010 |
Composable handler for State
effects. Handy for passing an updatable state
through a computation.
Some computations may not require the full power of State
effect:
- For a read-only state, see Control.Monad.Freer.Reader.
- To accumulate a value without using it on the way, see Control.Monad.Freer.Writer.
Using http://okmij.org/ftp/Haskell/extensible/Eff1.hs as a starting point.
Synopsis
- data State s r where
- get :: forall s effs. Member (State s) effs => Eff effs s
- put :: forall s effs. Member (State s) effs => s -> Eff effs ()
- modify :: forall s effs. Member (State s) effs => (s -> s) -> Eff effs ()
- gets :: forall s a effs. Member (State s) effs => (s -> a) -> Eff effs a
- runState :: forall s effs a. s -> Eff (State s ': effs) a -> Eff effs (a, s)
- evalState :: forall s effs a. s -> Eff (State s ': effs) a -> Eff effs a
- execState :: forall s effs a. s -> Eff (State s ': effs) a -> Eff effs s
- transactionState :: forall s effs a. Member (State s) effs => Eff effs a -> Eff effs a
- transactionState' :: forall s effs a. Member (State s) effs => Proxy s -> Eff effs a -> Eff effs a
State Effect
State Operations
get :: forall s effs. Member (State s) effs => Eff effs s Source #
Retrieve the current value of the state of type s :: *
.
put :: forall s effs. Member (State s) effs => s -> Eff effs () Source #
Set the current state to a specified value of type s :: *
.
modify :: forall s effs. Member (State s) effs => (s -> s) -> Eff effs () Source #
Modify the current state of type s :: *
using provided function
(s -> s)
.
gets :: forall s a effs. Member (State s) effs => (s -> a) -> Eff effs a Source #
Retrieve a specific component of the current state using the provided projection function.
State Handlers
runState :: forall s effs a. s -> Eff (State s ': effs) a -> Eff effs (a, s) Source #
Handler for State
effects.
evalState :: forall s effs a. s -> Eff (State s ': effs) a -> Eff effs a Source #
Run a State effect, discarding the final state.
execState :: forall s effs a. s -> Eff (State s ': effs) a -> Eff effs s Source #
Run a State
effect, returning only the final state.
State Utilities
transactionState :: forall s effs a. Member (State s) effs => Eff effs a -> Eff effs a Source #
An encapsulated State handler, for transactional semantics. The global
state is updated only if the transactionState
finished successfully.
GHC cannot infer the s
type parameter for this function, so it must be
specified explicitly with TypeApplications
. Alternatively, it can be
specified by supplying a Proxy
to transactionState'
.
transactionState' :: forall s effs a. Member (State s) effs => Proxy s -> Eff effs a -> Eff effs a Source #
Like transactionState
, but s
is specified by providing a Proxy
instead of requiring TypeApplications
.