in-other-words-0.2.1.1: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.AtomicState

Synopsis

Effects

data AtomicState s :: Effect where Source #

An effect for atomically reading and modifying a piece of state.

Convention: the interpreter for the AtomicState action must force the resulting tuple of the function, but not the end state or returned value.

Constructors

AtomicState :: (s -> (s, a)) -> AtomicState s m a 
AtomicGet :: AtomicState s m s 

Actions

atomicState :: Eff (AtomicState s) m => (s -> (s, a)) -> m a Source #

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

atomicState' :: Eff (AtomicState s) m => (s -> (s, a)) -> m a Source #

Atomically read and strictly modify the state.

The resulting state -- but not the value returned -- is forced.

atomicGet :: Eff (AtomicState s) m => m s Source #

Read the state.

Depending on the interperation of AtomicState, this can be more efficient than atomicState (\s -> (s,s))

atomicGets :: Eff (AtomicState s) m => (s -> a) -> m a Source #

atomicModify :: Eff (AtomicState s) m => (s -> s) -> m () Source #

Atomically modify the state.

The resulting state is not forced. atomicModify' is a strict version that does force it.

atomicModify' :: Eff (AtomicState s) m => (s -> s) -> m () Source #

Atomically and strictly modify the state.

This is a strict version of atomicModify.

atomicPut :: Eff (AtomicState s) m => s -> m () Source #

Atomically overwrite the state.

You typically don't want to use this, as atomicGet >>= atomicPut . f isn't atomic.

Interpretations

atomicStateToIO :: forall s m a. Eff (Embed IO) m => s -> InterpretReifiedC (AtomicState s) m a -> m (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.

This has a higher-rank type, as it makes use of InterpretReifiedC. This makes atomicStateToIO very difficult to use partially applied. In particular, it can't be composed using ..

If performance is secondary, consider using the slower atomicStateToIOSimple, which doesn't have a higher-rank type.

runAtomicStateIORef :: forall s m a. Eff (Embed IO) m => IORef s -> InterpretReifiedC (AtomicState s) m a -> m a Source #

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

This has a higher-rank type, as it makes use of InterpretReifiedC. This makes runAtomicStateIORef very difficult to use partially applied. In particular, it can't be composed using ..

If performance is secondary, consider using the slower runAtomicStateIORefSimple, which doesn't have a higher-rank type.

runAtomicStateTVar :: forall s m a. Eff (Embed IO) m => TVar s -> InterpretReifiedC (AtomicState s) m a -> m a Source #

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

This has a higher-rank type, as it makes use of InterpretReifiedC. This makes runAtomicStateTVar very difficult to use partially applied. In particular, it can't be composed using ..

If performance is secondary, consider using the slower runAtomicStateTVarSimple, which doesn't have a higher-rank type.

atomicStateToState :: Eff (State s) m => AtomicStateToStateC s m a -> m a Source #

Transform an AtomicState effect into a State effect, discarding atomicity.

Simple variants of interpretations

atomicStateToIOSimple :: forall s m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => s -> InterpretSimpleC (AtomicState s) m a -> m (s, a) Source #

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

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

This is a less performant version of runAtomicStateIORefSimple that doesn't have a higher-rank type, making it much easier to use partially applied.

runAtomicStateIORefSimple :: forall s m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => IORef s -> InterpretSimpleC (AtomicState s) m a -> m a Source #

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

This is a less performant version of runAtomicStateIORef that doesn't have a higher-rank type, making it much easier to use partially applied.

runAtomicStateTVarSimple :: forall s m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => TVar s -> InterpretSimpleC (AtomicState s) m a -> m a Source #

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

This is a less performant version of runAtomicStateIORef that doesn't have a higher-rank type, making it much easier to use partially applied.

Carriers

type AtomicStateToStateC s = InterpretC AtomicStateToStateH (AtomicState s) Source #