Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A carrier for the State
effect that refrains from evaluating its state until necessary. This is less efficient than Control.Carrier.State.Strict but allows some cyclic computations to terminate that would loop infinitely in a strict state carrier.
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
.
Since: 1.0.0.0
Lazy state carrier
runState :: s -> StateC s m a -> m (s, a) Source #
Run a lazy State
effect, yielding the result value and the final state. More programs terminate with lazy state than strict state, but injudicious use of lazy state may lead to thunk buildup.
runState
s (pure
a) =pure
(s, a)
runState
sget
=pure
(s, s)
runState
s (put
t) =pure
(t, ())
Since: 1.0.0.0
Since: 1.0.0.0
StateC (s -> m (s, a)) |
Instances
MonadTrans (StateC s) Source # | |
Defined in Control.Carrier.State.Lazy | |
MonadFail m => MonadFail (StateC s m) Source # | |
Defined in Control.Carrier.State.Lazy | |
MonadFix m => MonadFix (StateC s m) Source # | |
Defined in Control.Carrier.State.Lazy | |
MonadIO m => MonadIO (StateC s m) Source # | |
Defined in Control.Carrier.State.Lazy | |
(Alternative m, Monad m) => Alternative (StateC s m) Source # | |
Monad m => Applicative (StateC s m) Source # | |
Defined in Control.Carrier.State.Lazy | |
Functor m => Functor (StateC s m) Source # | |
Monad m => Monad (StateC s m) Source # | |
(Alternative m, Monad m) => MonadPlus (StateC s m) Source # | |
Algebra sig m => Algebra (State s :+: sig) (StateC s m) Source # | |
State effect
module Control.Effect.State