Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data State s m a where
- get :: forall a r. Member (State a) r => Sem r a
- gets :: Member (State s) r => (s -> a) -> Sem r a
- put :: forall s r. Member (State s) r => s -> Sem r ()
- modify :: Member (State s) r => (s -> s) -> Sem r ()
- runState :: s -> Sem (State s ': r) a -> Sem r (s, a)
- runLazyState :: s -> Sem (State s ': r) a -> Sem r (s, a)
- runStateInIORef :: forall s r a. Member (Lift IO) r => IORef s -> Sem (State s ': r) a -> Sem r a
- hoistStateIntoStateT :: Sem (State s ': r) a -> StateT s (Sem r) a
Effect
data State s m a where Source #
An effect for providing statefulness. Note that unlike mtl's
StateT
, there is no restriction that the State
effect corresponds necessarily to local state. It could could just as well
be interrpeted in terms of HTTP requests or database access.
Interpreters which require statefulness can reinterpret
themselves in terms of State
, and subsequently call runState
.
Instances
type DefiningModule (State :: Type -> k -> Type -> Type) Source # | |
Defined in Polysemy.State |
Actions
Interpretations
runLazyState :: s -> Sem (State s ': r) a -> Sem r (s, a) Source #
Run a State
effect with local state, lazily.
runStateInIORef :: forall s r a. Member (Lift IO) r => IORef s -> Sem (State s ': r) a -> Sem r a Source #