Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data State s :: Effect where
- state :: Eff (State s) m => (s -> (s, a)) -> m a
- state' :: Eff (State s) m => (s -> (s, a)) -> m a
- get :: Eff (State s) m => m s
- gets :: Eff (State s) m => (s -> a) -> m a
- put :: Eff (State s) m => s -> m ()
- modify :: Eff (State s) m => (s -> s) -> m ()
- modify' :: Eff (State s) m => (s -> s) -> m ()
- runState :: forall s m a p. (Carrier m, Threaders '[StateThreads] m p) => s -> StateC s m a -> m (s, a)
- evalState :: forall s m a p. (Carrier m, Threaders '[StateThreads] m p) => s -> StateC s m a -> m a
- execState :: forall s m a p. (Carrier m, Threaders '[StateThreads] m p) => s -> StateC s m a -> m s
- runStateLazy :: forall s m a p. (Carrier m, Threaders '[StateLazyThreads] m p) => s -> StateLazyC s m a -> m (s, a)
- evalStateLazy :: forall s m a p. (Carrier m, Threaders '[StateLazyThreads] m p) => s -> StateLazyC s m a -> m a
- execStateLazy :: forall s m a p. (Carrier m, Threaders '[StateLazyThreads] m p) => s -> StateLazyC s m a -> m s
- stateToIO :: forall s m a. Eff (Embed IO) m => s -> InterpretReifiedC (State s) m a -> m (s, a)
- runStateIORef :: forall s m a. Eff (Embed IO) m => IORef s -> InterpretReifiedC (State s) m a -> m a
- stateToIOSimple :: forall s m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => s -> InterpretSimpleC (State s) m a -> m (s, a)
- runStateIORefSimple :: forall s m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => IORef s -> InterpretSimpleC (State s) m a -> m a
- class (forall s. Threads (StateT s) p) => StateThreads p
- class (forall s. Threads (StateT s) p) => StateLazyThreads p
- data StateC s m a
- data StateLazyC s m a
Effect
data State s :: Effect where Source #
An effect for non-atomic stateful operations.
If you need atomicity, use AtomicState
instead.
Actions
state :: Eff (State s) m => (s -> (s, a)) -> m a Source #
Read and modify the state.
The resulting tuple of the computation is forced. You can control what parts of the computation are evaluated by tying their evaluation to the tuple.
state' :: Eff (State s) m => (s -> (s, a)) -> m a Source #
A variant of state
that forces the resulting state (but not the return value)
modify' :: Eff (State s) m => (s -> s) -> m () Source #
A variant of modify
that forces the resulting state.
Interpretations
runState :: forall s m a p. (Carrier m, Threaders '[StateThreads] m p) => s -> StateC s m a -> m (s, a) Source #
evalState :: forall s m a p. (Carrier m, Threaders '[StateThreads] m p) => s -> StateC s m a -> m a Source #
Runs a
effect purely, discarding
the end state.State
s
execState :: forall s m a p. (Carrier m, Threaders '[StateThreads] m p) => s -> StateC s m a -> m s Source #
Runs a
effect purely, discarding
the end result.State
s
runStateLazy :: forall s m a p. (Carrier m, Threaders '[StateLazyThreads] m p) => s -> StateLazyC s m a -> m (s, a) Source #
Runs a
effect purely and lazily.State
s
Derivs
(StateLazyC
s m) =State
s ':Derivs
m
Prims
(StateLazyC
e m) =Prims
m
evalStateLazy :: forall s m a p. (Carrier m, Threaders '[StateLazyThreads] m p) => s -> StateLazyC s m a -> m a Source #
Runs a
effect purely and lazily,
discarding the final state.State
s
execStateLazy :: forall s m a p. (Carrier m, Threaders '[StateLazyThreads] m p) => s -> StateLazyC s m a -> m s Source #
Runs a
effect purely and lazily,
discarding the end result.State
s
stateToIO :: forall s m a. Eff (Embed IO) m => s -> InterpretReifiedC (State s) m a -> m (s, a) Source #
Runs a
effect by transforming it into non-atomic
operations in IO.State
s
This has a higher-rank type, as it makes use of InterpretReifiedC
.
This makes stateToIO
very difficult to use partially applied.
In particular, it can't be composed using
..
If performance is secondary, consider using the slower
stateToIOSimple
, which doesn't have a higher-rank type.
runStateIORef :: forall s m a. Eff (Embed IO) m => IORef s -> InterpretReifiedC (State s) m a -> m a Source #
Runs a
effect by transforming it into non-atomic
operations over an State
sIORef
.
This has a higher-rank type, as it makes use of InterpretReifiedC
.
This makes runStateIORef
very difficult to use partially applied.
In particular, it can't be composed using
..
If performance is secondary, consider using the slower
runStateIORefSimple
, which doesn't have a higher-rank type.
Simple variants of interpretations
stateToIOSimple :: forall s m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => s -> InterpretSimpleC (State s) m a -> m (s, a) Source #
runStateIORefSimple :: forall s m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => IORef s -> InterpretSimpleC (State s) m a -> m a Source #
Runs a
effect by transforming it into non-atomic
operations over an State
sIORef
.
This is a less performant version of runStateIORef
that doesn't have
a higher-rank type, making it much easier to use partially applied.
Threading constraints
class (forall s. Threads (StateT s) p) => StateThreads p Source #
StateThreads
accepts the following primitive effects:
Regional
s
Optional
s
(whens
is a functor)BaseControl
b
ListenPrim
o
(wheno
is aMonoid
)WriterPrim
o
(wheno
is aMonoid
)ReaderPrim
i
Mask
Bracket
Fix
Split
Instances
(forall s. Threads (StateT s) p) => StateThreads p Source # | |
Defined in Control.Effect.Internal.State |
class (forall s. Threads (StateT s) p) => StateLazyThreads p Source #
StateLazyThreads
accepts the following primitive effects:
Regional
s
Optional
s
(whens
is a functor)BaseControl
b
ListenPrim
o
(wheno
is aMonoid
)WriterPrim
o
(wheno
is aMonoid
)ReaderPrim
i
Mask
Bracket
Fix
Split
Instances
(forall s. Threads (StateT s) p) => StateLazyThreads p Source # | |
Defined in Control.Effect.Internal.State |
Carriers
Instances
data StateLazyC s m a Source #