Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data State s (m :: * -> *) k
- get :: (Member (State s) sig, Carrier sig m) => m s
- gets :: (Member (State s) sig, Carrier sig m) => (s -> a) -> m a
- put :: (Member (State s) sig, Carrier sig m) => s -> m ()
- modify :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m ()
- modifyLazy :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m ()
- newtype StateC s m a = StateC {
- runStateC :: s -> m (s, a)
- runState :: s -> StateC s m a -> m (s, a)
- evalState :: forall s m a. Functor m => s -> StateC s m a -> m a
- execState :: forall s m a. Functor m => s -> StateC s m a -> m s
Documentation
get :: (Member (State s) sig, Carrier sig m) => m s Source #
Get the current state value.
snd (run (runState a get)) == a
gets :: (Member (State s) sig, Carrier sig m) => (s -> a) -> m a Source #
Project a function out of the current state value.
snd (run (runState a (gets (applyFun f)))) == applyFun f a
put :: (Member (State s) sig, Carrier sig m) => s -> m () Source #
Replace the state value with a new value.
fst (run (runState a (put b))) == b
snd (run (runState a (get <* put b))) == a
snd (run (runState a (put b *> get))) == b
modify :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m () Source #
Replace the state value with the result of applying a function to the current state value. This is strict in the new state.
fst (run (runState a (modify (+1)))) == (1 + a :: Integer)
modifyLazy :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m () Source #
Replace the state value with the result of applying a function to the current state value. This is lazy in the new state; injudicious use of this function may lead to space leaks.
Instances
MonadTrans (StateC s) Source # | |
Defined in Control.Effect.State.Strict | |
Monad m => Monad (StateC s m) Source # | |
Functor m => Functor (StateC s m) Source # | |
MonadFail m => MonadFail (StateC s m) Source # | |
Defined in Control.Effect.State.Strict | |
Monad m => Applicative (StateC s m) Source # | |
Defined in Control.Effect.State.Strict | |
MonadIO m => MonadIO (StateC s m) Source # | |
Defined in Control.Effect.State.Strict | |
(Alternative m, Monad m) => Alternative (StateC s m) Source # | |
(Alternative m, Monad m) => MonadPlus (StateC s m) Source # | |
(Carrier sig m, Effect sig) => Carrier (State s :+: sig) (StateC s m) Source # | |
runState :: s -> StateC s m a -> m (s, a) Source #
Run a State
effect starting from the passed value.
run (runState a (pure b)) == (a, b)