| Safe Haskell | None | 
|---|---|
| Language | GHC2021 | 
Control.Concurrent.Class.MonadSTM.Strict
Description
This module corresponds to STM in "stm" package
Synopsis
- module Control.Concurrent.Class.MonadSTM.Strict.TArray
 - module Control.Concurrent.Class.MonadSTM.Strict.TBQueue
 - module Control.Concurrent.Class.MonadSTM.Strict.TChan
 - module Control.Concurrent.Class.MonadSTM.Strict.TMVar
 - module Control.Concurrent.Class.MonadSTM.Strict.TQueue
 - module Control.Concurrent.Class.MonadSTM.Strict.TVar
 - class (Monad m, Monad (STM m)) => MonadSTM (m :: Type -> Type) where
 - type family STM (m :: Type -> Type) = (stm :: Type -> Type) | stm -> m
 - throwSTM :: forall (m :: Type -> Type) e a. (MonadSTM m, MonadThrow (STM m), Exception e) => e -> STM m a
 - class (MonadSTM m, Monad (InspectMonadSTM m)) => MonadInspectSTM (m :: Type -> Type) where
- type InspectMonadSTM (m :: Type -> Type) :: Type -> Type
 - inspectTVar :: proxy m -> TVar m a -> InspectMonadSTM m a
 - inspectTMVar :: proxy m -> TMVar m a -> InspectMonadSTM m (Maybe a)
 
 - type family InspectMonadSTM (m :: Type -> Type) :: Type -> Type
 - class MonadSTM m => MonadLabelledSTM (m :: Type -> Type)
 - class MonadInspectSTM m => MonadTraceSTM (m :: Type -> Type) where
- traceTSem :: proxy m -> TSem m -> (Maybe Integer -> Integer -> InspectMonadSTM m TraceValue) -> STM m ()
 - traceTSemIO :: TSem m -> (Maybe Integer -> Integer -> InspectMonadSTM m TraceValue) -> m ()
 
 - data TraceValue where
- TraceValue :: forall tr. Typeable tr => {..} -> TraceValue
 - pattern DontTrace :: TraceValue
 - pattern TraceDynamic :: () => Typeable tr => tr -> TraceValue
 - pattern TraceString :: String -> TraceValue
 
 
Documentation
class (Monad m, Monad (STM m)) => MonadSTM (m :: Type -> Type) where #
The STM primitives parametrised by a monad m.
Minimal complete definition
atomically, newTVar, readTVar, writeTVar, retry, orElse, newTMVar, newEmptyTMVar, takeTMVar, tryTakeTMVar, putTMVar, tryPutTMVar, readTMVar, tryReadTMVar, swapTMVar, writeTMVar, isEmptyTMVar, newTQueue, readTQueue, tryReadTQueue, peekTQueue, tryPeekTQueue, flushTQueue, writeTQueue, isEmptyTQueue, unGetTQueue, newTBQueue, readTBQueue, tryReadTBQueue, peekTBQueue, tryPeekTBQueue, flushTBQueue, writeTBQueue, lengthTBQueue, isEmptyTBQueue, isFullTBQueue, unGetTBQueue, newTSem, waitTSem, signalTSem, signalTSemN, newTChan, newBroadcastTChan, dupTChan, cloneTChan, readTChan, tryReadTChan, peekTChan, tryPeekTChan, writeTChan, unGetTChan, isEmptyTChan
Methods
atomically :: HasCallStack => STM m a -> m a #
Atomically run an STM computation.
See atomically.
See retry.
orElse :: STM m a -> STM m a -> STM m a #
See orElse.
Instances
throwSTM :: forall (m :: Type -> Type) e a. (MonadSTM m, MonadThrow (STM m), Exception e) => e -> STM m a #
throwIO specialised to stm monad.
class (MonadSTM m, Monad (InspectMonadSTM 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.
Methods
inspectTVar :: proxy m -> TVar m a -> InspectMonadSTM 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 -> InspectMonadSTM m (Maybe a) #
Return the value of a TMVar as an InspectMonad computation.
Instances
| MonadInspectSTM IO | |||||
Defined in Control.Monad.Class.MonadSTM.Internal Associated Types 
 Methods inspectTVar :: proxy IO -> TVar IO a -> InspectMonadSTM IO a # inspectTMVar :: proxy IO -> TMVar IO a -> InspectMonadSTM IO (Maybe a) #  | |||||
| MonadInspectSTM m => MonadInspectSTM (ReaderT r m) | |||||
Defined in Control.Monad.Class.MonadSTM.Internal Associated Types 
 Methods inspectTVar :: proxy (ReaderT r m) -> TVar (ReaderT r m) a -> InspectMonadSTM (ReaderT r m) a # inspectTMVar :: proxy (ReaderT r m) -> TMVar (ReaderT r m) a -> InspectMonadSTM (ReaderT r m) (Maybe a) #  | |||||
type family InspectMonadSTM (m :: Type -> Type) :: Type -> Type #
Instances
| type InspectMonadSTM IO | |
Defined in Control.Monad.Class.MonadSTM.Internal  | |
| type InspectMonadSTM (ReaderT r m) | |
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
Instances
| MonadLabelledSTM IO | noop instance  | 
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 () #  | |
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
Methods
traceTSem :: proxy m -> TSem m -> (Maybe Integer -> Integer -> InspectMonadSTM m TraceValue) -> STM m () #
default traceTSem :: TSem m ~ TSemDefault m => proxy m -> TSem m -> (Maybe Integer -> Integer -> InspectMonadSTM m TraceValue) -> STM m () #
traceTSemIO :: TSem m -> (Maybe Integer -> Integer -> InspectMonadSTM m TraceValue) -> m () #
default traceTSemIO :: TSem m -> (Maybe Integer -> Integer -> InspectMonadSTM m TraceValue) -> m () #
Instances
| MonadTraceSTM IO | noop instance  | 
Defined in Control.Monad.Class.MonadSTM.Internal Methods traceTVar :: proxy IO -> TVar IO a -> (Maybe a -> a -> InspectMonadSTM IO TraceValue) -> STM IO () # traceTMVar :: proxy IO -> TMVar IO a -> (Maybe (Maybe a) -> Maybe a -> InspectMonadSTM IO TraceValue) -> STM IO () # traceTQueue :: proxy IO -> TQueue IO a -> (Maybe [a] -> [a] -> InspectMonadSTM IO TraceValue) -> STM IO () # traceTBQueue :: proxy IO -> TBQueue IO a -> (Maybe [a] -> [a] -> InspectMonadSTM IO TraceValue) -> STM IO () # traceTSem :: proxy IO -> TSem IO -> (Maybe Integer -> Integer -> InspectMonadSTM IO TraceValue) -> STM IO () # traceTVarIO :: TVar IO a -> (Maybe a -> a -> InspectMonadSTM IO TraceValue) -> IO () # traceTMVarIO :: TMVar IO a -> (Maybe (Maybe a) -> Maybe a -> InspectMonadSTM IO TraceValue) -> IO () # traceTQueueIO :: TQueue IO a -> (Maybe [a] -> [a] -> InspectMonadSTM IO TraceValue) -> IO () # traceTBQueueIO :: TBQueue IO a -> (Maybe [a] -> [a] -> InspectMonadSTM IO TraceValue) -> IO () # traceTSemIO :: TSem IO -> (Maybe Integer -> Integer -> InspectMonadSTM IO TraceValue) -> IO () #  | |
| MonadTraceSTM m => MonadTraceSTM (ReaderT r m) | |
Defined in Control.Monad.Class.MonadSTM.Internal Methods traceTVar :: proxy (ReaderT r m) -> TVar (ReaderT r m) a -> (Maybe a -> a -> InspectMonadSTM (ReaderT r m) TraceValue) -> STM (ReaderT r m) () # traceTMVar :: proxy (ReaderT r m) -> TMVar (ReaderT r m) a -> (Maybe (Maybe a) -> Maybe a -> InspectMonadSTM (ReaderT r m) TraceValue) -> STM (ReaderT r m) () # traceTQueue :: proxy (ReaderT r m) -> TQueue (ReaderT r m) a -> (Maybe [a] -> [a] -> InspectMonadSTM (ReaderT r m) TraceValue) -> STM (ReaderT r m) () # traceTBQueue :: proxy (ReaderT r m) -> TBQueue (ReaderT r m) a -> (Maybe [a] -> [a] -> InspectMonadSTM (ReaderT r m) TraceValue) -> STM (ReaderT r m) () # traceTSem :: proxy (ReaderT r m) -> TSem (ReaderT r m) -> (Maybe Integer -> Integer -> InspectMonadSTM (ReaderT r m) TraceValue) -> STM (ReaderT r m) () # traceTVarIO :: TVar (ReaderT r m) a -> (Maybe a -> a -> InspectMonadSTM (ReaderT r m) TraceValue) -> ReaderT r m () # traceTMVarIO :: TMVar (ReaderT r m) a -> (Maybe (Maybe a) -> Maybe a -> InspectMonadSTM (ReaderT r m) TraceValue) -> ReaderT r m () # traceTQueueIO :: TQueue (ReaderT r m) a -> (Maybe [a] -> [a] -> InspectMonadSTM (ReaderT r m) TraceValue) -> ReaderT r m () # traceTBQueueIO :: TBQueue (ReaderT r m) a -> (Maybe [a] -> [a] -> InspectMonadSTM (ReaderT r m) TraceValue) -> ReaderT r m () # traceTSemIO :: TSem (ReaderT r m) -> (Maybe Integer -> Integer -> InspectMonadSTM (ReaderT r m) TraceValue) -> ReaderT r m () #  | |
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 TraceDynamic :: () => Typeable tr => tr -> TraceValue | Use only a dynamic tracer.  | 
| pattern TraceString :: String -> TraceValue | Use only string tracing.  |