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

Control.Concurrent.Class.MonadSTM.Strict

Description

This module corresponds to STM in "stm" package

Synopsis

Documentation

class (Monad m, Monad (STM m)) => MonadSTM (m :: Type -> Type) where #

The STM primitives parametrised by a monad m.

Associated Types

type STM (m :: Type -> Type) = (stm :: Type -> Type) | stm -> m #

The STM monad.

Methods

atomically :: HasCallStack => STM m a -> m a #

Atomically run an STM computation.

See atomically.

retry :: STM m a #

See retry.

orElse :: STM m a -> STM m a -> STM m a #

See orElse.

check :: Bool -> STM m () #

See check.

Instances

Instances details
MonadSTM IO 
Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

Associated Types

type STM IO = (stm :: Type -> Type) #

type TVar IO :: Type -> Type #

type TMVar IO :: Type -> Type #

type TQueue IO :: Type -> Type #

type TBQueue IO :: Type -> Type #

type TArray IO :: Type -> Type -> Type #

type TSem IO #

type TChan IO :: Type -> Type #

Methods

atomically :: HasCallStack => STM IO a -> IO a #

newTVar :: a -> STM IO (TVar IO a) #

readTVar :: TVar IO a -> STM IO a #

writeTVar :: TVar IO a -> a -> STM IO () #

retry :: STM IO a #

orElse :: STM IO a -> STM IO a -> STM IO a #

modifyTVar :: TVar IO a -> (a -> a) -> STM IO () #

modifyTVar' :: TVar IO a -> (a -> a) -> STM IO () #

stateTVar :: TVar IO s -> (s -> (a, s)) -> STM IO a #

swapTVar :: TVar IO a -> a -> STM IO a #

check :: Bool -> STM IO () #

newTMVar :: a -> STM IO (TMVar IO a) #

newEmptyTMVar :: STM IO (TMVar IO a) #

takeTMVar :: TMVar IO a -> STM IO a #

tryTakeTMVar :: TMVar IO a -> STM IO (Maybe a) #

putTMVar :: TMVar IO a -> a -> STM IO () #

tryPutTMVar :: TMVar IO a -> a -> STM IO Bool #

readTMVar :: TMVar IO a -> STM IO a #

tryReadTMVar :: TMVar IO a -> STM IO (Maybe a) #

swapTMVar :: TMVar IO a -> a -> STM IO a #

isEmptyTMVar :: TMVar IO a -> STM IO Bool #

newTQueue :: STM IO (TQueue IO a) #

readTQueue :: TQueue IO a -> STM IO a #

tryReadTQueue :: TQueue IO a -> STM IO (Maybe a) #

peekTQueue :: TQueue IO a -> STM IO a #

tryPeekTQueue :: TQueue IO a -> STM IO (Maybe a) #

flushTQueue :: TQueue IO a -> STM IO [a] #

writeTQueue :: TQueue IO a -> a -> STM IO () #

isEmptyTQueue :: TQueue IO a -> STM IO Bool #

unGetTQueue :: TQueue IO a -> a -> STM IO () #

newTBQueue :: Natural -> STM IO (TBQueue IO a) #

readTBQueue :: TBQueue IO a -> STM IO a #

tryReadTBQueue :: TBQueue IO a -> STM IO (Maybe a) #

peekTBQueue :: TBQueue IO a -> STM IO a #

tryPeekTBQueue :: TBQueue IO a -> STM IO (Maybe a) #

flushTBQueue :: TBQueue IO a -> STM IO [a] #

writeTBQueue :: TBQueue IO a -> a -> STM IO () #

lengthTBQueue :: TBQueue IO a -> STM IO Natural #

isEmptyTBQueue :: TBQueue IO a -> STM IO Bool #

isFullTBQueue :: TBQueue IO a -> STM IO Bool #

unGetTBQueue :: TBQueue IO a -> a -> STM IO () #

newTSem :: Integer -> STM IO (TSem IO) #

waitTSem :: TSem IO -> STM IO () #

signalTSem :: TSem IO -> STM IO () #

signalTSemN :: Natural -> TSem IO -> STM IO () #

newTChan :: STM IO (TChan IO a) #

newBroadcastTChan :: STM IO (TChan IO a) #

dupTChan :: TChan IO a -> STM IO (TChan IO a) #

cloneTChan :: TChan IO a -> STM IO (TChan IO a) #

readTChan :: TChan IO a -> STM IO a #

tryReadTChan :: TChan IO a -> STM IO (Maybe a) #

peekTChan :: TChan IO a -> STM IO a #

tryPeekTChan :: TChan IO a -> STM IO (Maybe a) #

writeTChan :: TChan IO a -> a -> STM IO () #

unGetTChan :: TChan IO a -> a -> STM IO () #

isEmptyTChan :: TChan IO a -> STM IO Bool #

newTVarIO :: a -> IO (TVar IO a) #

readTVarIO :: TVar IO a -> IO a #

newTMVarIO :: a -> IO (TMVar IO a) #

newEmptyTMVarIO :: IO (TMVar IO a) #

newTQueueIO :: IO (TQueue IO a) #

newTBQueueIO :: Natural -> IO (TBQueue IO a) #

newTChanIO :: IO (TChan IO a) #

newBroadcastTChanIO :: IO (TChan IO a) #

MonadSTM m => MonadSTM (ReaderT r m)

The underlying stm monad is also transformed.

Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

Associated Types

type STM (ReaderT r m) = (stm :: Type -> Type) #

type TVar (ReaderT r m) :: Type -> Type #

type TMVar (ReaderT r m) :: Type -> Type #

type TQueue (ReaderT r m) :: Type -> Type #

type TBQueue (ReaderT r m) :: Type -> Type #

type TArray (ReaderT r m) :: Type -> Type -> Type #

type TSem (ReaderT r m) #

type TChan (ReaderT r m) :: Type -> Type #

Methods

atomically :: HasCallStack => STM (ReaderT r m) a -> ReaderT r m a #

newTVar :: a -> STM (ReaderT r m) (TVar (ReaderT r m) a) #

readTVar :: TVar (ReaderT r m) a -> STM (ReaderT r m) a #

writeTVar :: TVar (ReaderT r m) a -> a -> STM (ReaderT r m) () #

retry :: STM (ReaderT r m) a #

orElse :: STM (ReaderT r m) a -> STM (ReaderT r m) a -> STM (ReaderT r m) a #

modifyTVar :: TVar (ReaderT r m) a -> (a -> a) -> STM (ReaderT r m) () #

modifyTVar' :: TVar (ReaderT r m) a -> (a -> a) -> STM (ReaderT r m) () #

stateTVar :: TVar (ReaderT r m) s -> (s -> (a, s)) -> STM (ReaderT r m) a #

swapTVar :: TVar (ReaderT r m) a -> a -> STM (ReaderT r m) a #

check :: Bool -> STM (ReaderT r m) () #

newTMVar :: a -> STM (ReaderT r m) (TMVar (ReaderT r m) a) #

newEmptyTMVar :: STM (ReaderT r m) (TMVar (ReaderT r m) a) #

takeTMVar :: TMVar (ReaderT r m) a -> STM (ReaderT r m) a #

tryTakeTMVar :: TMVar (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

putTMVar :: TMVar (ReaderT r m) a -> a -> STM (ReaderT r m) () #

tryPutTMVar :: TMVar (ReaderT r m) a -> a -> STM (ReaderT r m) Bool #

readTMVar :: TMVar (ReaderT r m) a -> STM (ReaderT r m) a #

tryReadTMVar :: TMVar (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

swapTMVar :: TMVar (ReaderT r m) a -> a -> STM (ReaderT r m) a #

isEmptyTMVar :: TMVar (ReaderT r m) a -> STM (ReaderT r m) Bool #

newTQueue :: STM (ReaderT r m) (TQueue (ReaderT r m) a) #

readTQueue :: TQueue (ReaderT r m) a -> STM (ReaderT r m) a #

tryReadTQueue :: TQueue (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

peekTQueue :: TQueue (ReaderT r m) a -> STM (ReaderT r m) a #

tryPeekTQueue :: TQueue (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

flushTQueue :: TQueue (ReaderT r m) a -> STM (ReaderT r m) [a] #

writeTQueue :: TQueue (ReaderT r m) a -> a -> STM (ReaderT r m) () #

isEmptyTQueue :: TQueue (ReaderT r m) a -> STM (ReaderT r m) Bool #

unGetTQueue :: TQueue (ReaderT r m) a -> a -> STM (ReaderT r m) () #

newTBQueue :: Natural -> STM (ReaderT r m) (TBQueue (ReaderT r m) a) #

readTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) a #

tryReadTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

peekTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) a #

tryPeekTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

flushTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) [a] #

writeTBQueue :: TBQueue (ReaderT r m) a -> a -> STM (ReaderT r m) () #

lengthTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) Natural #

isEmptyTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) Bool #

isFullTBQueue :: TBQueue (ReaderT r m) a -> STM (ReaderT r m) Bool #

unGetTBQueue :: TBQueue (ReaderT r m) a -> a -> STM (ReaderT r m) () #

newTSem :: Integer -> STM (ReaderT r m) (TSem (ReaderT r m)) #

waitTSem :: TSem (ReaderT r m) -> STM (ReaderT r m) () #

signalTSem :: TSem (ReaderT r m) -> STM (ReaderT r m) () #

signalTSemN :: Natural -> TSem (ReaderT r m) -> STM (ReaderT r m) () #

newTChan :: STM (ReaderT r m) (TChan (ReaderT r m) a) #

newBroadcastTChan :: STM (ReaderT r m) (TChan (ReaderT r m) a) #

dupTChan :: TChan (ReaderT r m) a -> STM (ReaderT r m) (TChan (ReaderT r m) a) #

cloneTChan :: TChan (ReaderT r m) a -> STM (ReaderT r m) (TChan (ReaderT r m) a) #

readTChan :: TChan (ReaderT r m) a -> STM (ReaderT r m) a #

tryReadTChan :: TChan (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

peekTChan :: TChan (ReaderT r m) a -> STM (ReaderT r m) a #

tryPeekTChan :: TChan (ReaderT r m) a -> STM (ReaderT r m) (Maybe a) #

writeTChan :: TChan (ReaderT r m) a -> a -> STM (ReaderT r m) () #

unGetTChan :: TChan (ReaderT r m) a -> a -> STM (ReaderT r m) () #

isEmptyTChan :: TChan (ReaderT r m) a -> STM (ReaderT r m) Bool #

newTVarIO :: a -> ReaderT r m (TVar (ReaderT r m) a) #

readTVarIO :: TVar (ReaderT r m) a -> ReaderT r m a #

newTMVarIO :: a -> ReaderT r m (TMVar (ReaderT r m) a) #

newEmptyTMVarIO :: ReaderT r m (TMVar (ReaderT r m) a) #

newTQueueIO :: ReaderT r m (TQueue (ReaderT r m) a) #

newTBQueueIO :: Natural -> ReaderT r m (TBQueue (ReaderT r m) a) #

newTChanIO :: ReaderT r m (TChan (ReaderT r m) a) #

newBroadcastTChanIO :: ReaderT r m (TChan (ReaderT r m) a) #

type family STM (m :: Type -> Type) = (stm :: Type -> Type) | stm -> m #

The STM monad.

Instances

Instances details
type STM IO 
Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

type STM IO = STM
type STM (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

type STM (ReaderT r m) = ReaderT r (STM m)

class MonadInspectSTM m => MonadTraceSTM (m :: Type -> Type) where #

MonadTraceSTM allows to trace values of stm variables when stm transaction is committed. This allows to verify invariants when a variable is committed.

Minimal complete definition

traceTVar, traceTQueue, traceTBQueue

Methods

traceTSem :: proxy m -> TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> STM m () #

traceTSemIO :: TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> m () #

Instances

Instances details
MonadTraceSTM IO

noop instance

Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

Methods

traceTVar :: proxy IO -> TVar IO a -> (Maybe a -> a -> InspectMonad IO TraceValue) -> STM IO () #

traceTMVar :: proxy IO -> TMVar IO a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad IO TraceValue) -> STM IO () #

traceTQueue :: proxy IO -> TQueue IO a -> (Maybe [a] -> [a] -> InspectMonad IO TraceValue) -> STM IO () #

traceTBQueue :: proxy IO -> TBQueue IO a -> (Maybe [a] -> [a] -> InspectMonad IO TraceValue) -> STM IO () #

traceTSem :: proxy IO -> TSem IO -> (Maybe Integer -> Integer -> InspectMonad IO TraceValue) -> STM IO () #

traceTVarIO :: TVar IO a -> (Maybe a -> a -> InspectMonad IO TraceValue) -> IO () #

traceTMVarIO :: TMVar IO a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad IO TraceValue) -> IO () #

traceTQueueIO :: TQueue IO a -> (Maybe [a] -> [a] -> InspectMonad IO TraceValue) -> IO () #

traceTBQueueIO :: TBQueue IO a -> (Maybe [a] -> [a] -> InspectMonad IO TraceValue) -> IO () #

traceTSemIO :: TSem IO -> (Maybe Integer -> Integer -> InspectMonad IO TraceValue) -> IO () #

data TraceValue where #

A GADT which instructs how to trace the value. The traceDynamic will use dynamic tracing, e.g. "Control.Monad.IOSim.traceM"; while traceString will be traced with EventSay. The IOSims dynamic tracing allows to recover the value from the simulation trace (see "Control.Monad.IOSim.selectTraceEventsDynamic").

Constructors

TraceValue 

Fields

Bundled Patterns

pattern DontTrace :: TraceValue

Do not trace the value.

pattern TraceString :: String -> TraceValue

Use only string tracing.

pattern TraceDynamic :: () => Typeable tr => tr -> TraceValue

Use only a dynamic tracer.

class (MonadSTM m, Monad (InspectMonad m)) => MonadInspectSTM (m :: Type -> Type) where #

This type class is indented for 'io-sim', where one might want to access a TVar in the underlying ST monad.

Associated Types

type InspectMonad (m :: Type -> Type) :: Type -> Type #

Methods

inspectTVar :: proxy m -> TVar m a -> InspectMonad m a #

Return the value of a TVar as an InspectMonad computation.

inspectTVar is useful if the value of a TVar observed by traceTVar contains other TVars.

inspectTMVar :: proxy m -> TMVar m a -> InspectMonad m (Maybe a) #

Return the value of a MonadSTM as an InspectMonad computation.

Instances

Instances details
MonadInspectSTM IO 
Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

Associated Types

type InspectMonad IO :: Type -> Type #

Methods

inspectTVar :: proxy IO -> TVar IO a -> InspectMonad IO a #

inspectTMVar :: proxy IO -> TMVar IO a -> InspectMonad IO (Maybe a) #

type family InspectMonad (m :: Type -> Type) :: Type -> Type #

Instances

Instances details
type InspectMonad IO 
Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

class MonadSTM m => MonadLabelledSTM (m :: Type -> Type) #

Labelled TVars & friends.

The IO instances is no-op, the IOSim instance enhances simulation trace. This is very useful when analysing low lever concurrency issues (e.g. deadlocks, livelocks etc).

Minimal complete definition

labelTVar

Instances

Instances details
MonadLabelledSTM IO

noop instance

Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

Methods

labelTVar :: TVar IO a -> String -> STM IO () #

labelTMVar :: TMVar IO a -> String -> STM IO () #

labelTQueue :: TQueue IO a -> String -> STM IO () #

labelTBQueue :: TBQueue IO a -> String -> STM IO () #

labelTArray :: (Ix i, Show i) => TArray IO i e -> String -> STM IO () #

labelTSem :: TSem IO -> String -> STM IO () #

labelTChan :: TChan IO a -> String -> STM IO () #

labelTVarIO :: TVar IO a -> String -> IO () #

labelTMVarIO :: TMVar IO a -> String -> IO () #

labelTQueueIO :: TQueue IO a -> String -> IO () #

labelTBQueueIO :: TBQueue IO a -> String -> IO () #

labelTArrayIO :: (Ix i, Show i) => TArray IO i e -> String -> IO () #

labelTSemIO :: TSem IO -> String -> IO () #

labelTChanIO :: TChan IO a -> String -> IO () #

data StrictTArray m i e Source #

Instances

Instances details
(MArray (TArray m) e stm, Monad stm) => MArray (StrictTArray m) e stm Source # 
Instance details

Defined in Control.Concurrent.Class.MonadSTM.Strict.TArray

Methods

getBounds :: Ix i => StrictTArray m i e -> stm (i, i) #

getNumElements :: Ix i => StrictTArray m i e -> stm Int

newArray :: Ix i => (i, i) -> e -> stm (StrictTArray m i e) #

newArray_ :: Ix i => (i, i) -> stm (StrictTArray m i e) #

unsafeNewArray_ :: Ix i => (i, i) -> stm (StrictTArray m i e)

unsafeRead :: Ix i => StrictTArray m i e -> Int -> stm e

unsafeWrite :: Ix i => StrictTArray m i e -> Int -> e -> stm ()

type LazyTChan m = TChan m Source #

data StrictTMVar m a Source #

TMVar that keeps its value in WHNF at all times

type LazyTMVar m = TMVar m Source #

type LazyTVar m = TVar m Source #

newTMVarIO :: MonadSTM m => a -> m (StrictTMVar m a) Source #

throwSTM :: forall (m :: Type -> Type) e a. (MonadSTM m, MonadThrow (STM m), Exception e) => e -> STM m a #

throwIO specialised to stm monad.

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

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

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

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

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

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

traceTQueue :: MonadTraceSTM m => proxy m -> StrictTQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> STM m () Source #

traceTBQueue :: MonadTraceSTM m => proxy m -> StrictTBQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> STM m () Source #

traceTQueueIO :: MonadTraceSTM m => StrictTQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> 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 #

newTMVar :: MonadSTM m => a -> STM m (StrictTMVar m a) Source #

putTMVar :: MonadSTM m => StrictTMVar m a -> a -> STM m () Source #

swapTMVar :: MonadSTM m => StrictTMVar m a -> a -> STM m a Source #

writeTQueue :: MonadSTM m => StrictTQueue m a -> a -> STM m () Source #

unGetTQueue :: MonadSTM m => StrictTQueue m a -> a -> STM m () Source #

writeTBQueue :: MonadSTM m => StrictTBQueue m a -> a -> STM m () Source #

unGetTBQueue :: MonadSTM m => StrictTBQueue m a -> a -> STM m () Source #

writeTChan :: MonadSTM m => StrictTChan m a -> a -> STM m () Source #

unGetTChan :: MonadSTM m => StrictTChan m a -> a -> STM 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.

castStrictTVar :: LazyTVar m ~ LazyTVar n => StrictTVar m a -> StrictTVar n a Source #

Cast the monad if both use the same representation of TVars.

This function is useful for monad transformers stacks if the TVar is used in different monad stacks.