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

Safe HaskellNone
LanguageHaskell2010

Polysemy.AtomicState

Contents

Synopsis

Effect

data AtomicState s m a where Source #

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' :: 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 #

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 :: 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.

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.