polysemy-1.1.0.0: Higher-order, low-boilerplate, zero-cost free monads.

Safe HaskellNone
LanguageHaskell2010

Polysemy.State

Contents

Synopsis

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.

Constructors

Get :: State s m s 
Put :: s -> State s m () 
Instances
type DefiningModule (State :: Type -> k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.State

type DefiningModule (State :: Type -> k -> Type -> Type) = "Polysemy.State"

Actions

get :: forall s r. MemberWithError (State s) r => Sem r s Source #

gets :: forall s a r. Member (State s) r => (s -> a) -> Sem r a Source #

put :: forall s r. MemberWithError (State s) r => s -> Sem r () Source #

modify :: Member (State s) r => (s -> s) -> Sem r () Source #

modify' :: Member (State s) r => (s -> s) -> Sem r () Source #

A variant of modify in which the computation is strict in the new state.

Interpretations

runState :: s -> Sem (State s ': r) a -> Sem r (s, a) Source #

Run a State effect with local state.

evalState :: s -> Sem (State s ': r) a -> Sem r a Source #

Run a State effect with local state.

Since: 1.0.0.0

runLazyState :: s -> Sem (State s ': r) a -> Sem r (s, a) Source #

Run a State effect with local state, lazily.

evalLazyState :: s -> Sem (State s ': r) a -> Sem r a Source #

Run a State effect with local state, lazily.

Since: 1.0.0.0

runStateIORef :: forall s r a. Member (Embed IO) r => IORef s -> Sem (State s ': r) a -> Sem r a Source #

Run a State effect by transforming it into operations over an IORef.

Note: This is not safe in a concurrent setting, as modify isn't atomic. If you need operations over the state to be atomic, use runAtomicStateIORef or runAtomicStateTVar instead.

Since: 1.0.0.0

Interoperation with MTL

hoistStateIntoStateT :: Sem (State s ': r) a -> StateT s (Sem r) a Source #

Hoist a State effect into a StateT monad transformer. This can be useful when writing interpreters that need to interop with MTL.

Since: 0.1.3.0