Safe Haskell | None |
---|---|
Language | Haskell2010 |
A carrier for the State
effect. It uses an IORef
internally to handle its state, and thus is safe to use with Control.Carrier.Resource. Underlying IORef
operations are performed with readIORef
and writeIORef
.
Note that the parameter order in runState
, evalState
, and execState
is reversed compared the equivalent functions provided by transformers
. This is an intentional decision made to enable the composition of effect handlers with .
without invoking flip
.
Strict state carrier
runState :: MonadIO m => 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)
Since: 1.0.0.0
evalState :: forall s m a. MonadIO m => s -> StateC s m a -> m a Source #
Run a State
effect, yielding the result value and discarding the final state.
run (evalState a (pure b)) === b
Since: 1.0.0.0
execState :: forall s m a. MonadIO m => s -> StateC s m a -> m s Source #
Run a State
effect, yielding the final state and discarding the return value.
run (execState a (pure b)) === a
Since: 1.0.0.0
Since: 1.0.0.0
Instances
Monad m => Monad (StateC s m) Source # | |
Functor m => Functor (StateC s m) Source # | |
MonadFix m => MonadFix (StateC s m) Source # | |
Defined in Control.Carrier.State.IORef | |
MonadFail m => MonadFail (StateC s m) Source # | |
Defined in Control.Carrier.State.IORef | |
Applicative m => Applicative (StateC s m) Source # | |
Defined in Control.Carrier.State.IORef | |
MonadIO m => MonadIO (StateC s m) Source # | |
Defined in Control.Carrier.State.IORef | |
Alternative m => Alternative (StateC s m) Source # | |
(Alternative m, Monad m) => MonadPlus (StateC s m) Source # | |
(MonadIO m, Algebra sig m, Effect sig) => Algebra (State s :+: sig) (StateC s m) Source # | |
State effect
module Control.Effect.State