strict-stm-1.1.0.1: Strict STM interface polymorphic over stm implementation.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Concurrent.Class.MonadSTM.Strict.TVar

Description

This module corresponds to TVar in "stm" package

Synopsis

StrictTVar

type LazyTVar m = TVar m Source #

toLazyTVar :: StrictTVar m a -> LazyTVar m a Source #

Get the underlying TVar

Since we obviously cannot guarantee that updates to this LazyTVar will be strict, this should be used with caution.

newTVar :: MonadSTM m => a -> STM m (StrictTVar m a) Source #

newTVarIO :: MonadSTM m => a -> m (StrictTVar m a) Source #

newTVarWithInvariant Source #

Arguments

:: (MonadSTM m, HasCallStack) 
=> (a -> Maybe String)

Invariant (expect Nothing)

-> a 
-> STM m (StrictTVar m a) 

newTVarWithInvariantIO Source #

Arguments

:: (MonadSTM m, HasCallStack) 
=> (a -> Maybe String)

Invariant (expect Nothing)

-> a 
-> m (StrictTVar m a) 

readTVar :: MonadSTM m => StrictTVar m a -> STM m a Source #

writeTVar :: (MonadSTM m, HasCallStack) => StrictTVar m a -> a -> STM m () Source #

modifyTVar :: MonadSTM m => StrictTVar m a -> (a -> a) -> STM m () Source #

stateTVar :: MonadSTM m => StrictTVar m s -> (s -> (a, s)) -> STM m a Source #

swapTVar :: MonadSTM m => StrictTVar m a -> a -> STM m a Source #

check :: MonadSTM m => Bool -> STM m () #

See check.

Low-level API

checkInvariant :: HasCallStack => Maybe String -> a -> a Source #

Check invariant (if enabled) before continuing

checkInvariant mErr x is equal to x if mErr == Nothing, and throws an error err if mErr == Just err.

This is exported so that other code that wants to conditionally check invariants can reuse the same logic, rather than having to introduce new per-package flags.

MonadLabelSTM

MonadTraceSTM

traceTVar :: MonadTraceSTM m => proxy m -> StrictTVar m a -> (Maybe a -> a -> InspectMonad m TraceValue) -> STM m () Source #