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

Safe HaskellNone
LanguageHaskell2010

Polysemy.AtomicState

Contents

Synopsis

Effect

data AtomicState s m a where Source #

A variant of State that supports atomic operations.

Since: 1.1.0.0

Constructors

AtomicState :: (s -> (s, a)) -> AtomicState s m a 
AtomicGet :: AtomicState s m s 
Instances
type DefiningModule (AtomicState :: Type -> k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.AtomicState

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

Actions

atomicState :: forall s a r. Member (AtomicState s) r => (s -> (s, a)) -> Sem r a Source #

Atomically reads and modifies the state.

atomicState' :: forall s a r. Member (AtomicState s) r => (s -> (s, a)) -> Sem r a Source #

A variant of atomicState in which the computation is strict in the new state and return value.

atomicGet :: forall s r. Member (AtomicState s) r => Sem r s Source #

atomicGets :: forall s s' r. Member (AtomicState s) r => (s -> s') -> Sem r s' Source #

Since: 1.2.2.0

atomicPut :: Member (AtomicState s) r => s -> Sem r () Source #

atomicModify :: Member (AtomicState s) r => (s -> s) -> Sem r () Source #

atomicModify' :: Member (AtomicState s) r => (s -> s) -> Sem r () Source #

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

Interpretations

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

Run an AtomicState effect by transforming it into atomic operations over an IORef.

runAtomicStateTVar :: Member (Embed IO) r => TVar s -> Sem (AtomicState s ': r) a -> Sem r a Source #

Run an AtomicState effect by transforming it into atomic operations over a TVar.

atomicStateToIO :: forall s r a. Member (Embed IO) r => s -> Sem (AtomicState s ': r) a -> Sem r (s, a) Source #

Run an AtomicState effect in terms of atomic operations in IO.

Internally, this simply creates a new IORef, passes it to runAtomicStateIORef, and then returns the result and the final value of the IORef.

Beware: As this uses an IORef internally, all other effects will have local state semantics in regards to AtomicState effects interpreted this way. For example, throw and catch will never revert atomicModifys, even if runError is used after atomicStateToIO.

Since: 1.2.0.0

atomicStateToState :: Member (State s) r => Sem (AtomicState s ': r) a -> Sem r a Source #

Transform an AtomicState effect to a State effect, discarding the notion of atomicity.