Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Control.Monad.Class.MonadSTM
Contents
Description
This module corresponds to Control.Monad.STM in "stm" package
Synopsis
- class (Monad m, Monad (STM m)) => MonadSTM m where
- throwSTM :: (MonadSTM m, MonadThrow (STM m), Exception e) => e -> STM m a
- class MonadSTM m => MonadLabelledSTM m
- class MonadInspectSTM m => MonadTraceSTM m where
- traceTVar :: proxy m -> TVar m a -> (Maybe a -> a -> InspectMonad m TraceValue) -> STM m ()
- traceTMVar :: proxy m -> TMVar m a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad m TraceValue) -> STM m ()
- traceTQueue :: proxy m -> TQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> STM m ()
- traceTBQueue :: proxy m -> TBQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> STM m ()
- traceTSem :: proxy m -> TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> STM m ()
- traceTVarIO :: TVar m a -> (Maybe a -> a -> InspectMonad m TraceValue) -> m ()
- traceTMVarIO :: TMVar m a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad m TraceValue) -> m ()
- traceTQueueIO :: TQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> m ()
- traceTBQueueIO :: TBQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> m ()
- traceTSemIO :: TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> m ()
- data TraceValue where
- TraceValue :: forall tr. Typeable tr => {..} -> TraceValue
- pattern TraceDynamic :: () => forall tr. Typeable tr => tr -> TraceValue
- pattern TraceString :: String -> TraceValue
- pattern DontTrace :: TraceValue
- class (MonadSTM m, Monad (InspectMonad m)) => MonadInspectSTM m where
- type InspectMonad m :: Type -> Type
- inspectTVar :: proxy m -> TVar m a -> InspectMonad m a
- inspectTMVar :: proxy m -> TMVar m a -> InspectMonad m (Maybe a)
Documentation
class (Monad m, Monad (STM m)) => MonadSTM m where Source #
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, 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 Source #
Atomically run an STM computation.
See atomically
.
See retry
.
orElse :: STM m a -> STM m a -> STM m a Source #
See orElse
.
check :: Bool -> STM m () Source #
See check
.
Instances
throwSTM :: (MonadSTM m, MonadThrow (STM m), Exception e) => e -> STM m a Source #
throwIO
specialised to stm
monad.
non standard extensions
The non standard extensions include MonadLabelledSTM
and MonadTraceSTM
/
MonadInspectSTM
. For IO
these are all no-op, however they greatly
enhance IOSim
capabilities.
They are not only useful for debugging concurrency issues, but also to write
testable properties.
class MonadSTM m => MonadLabelledSTM m Source #
Labelled TVar
s & 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 Source # | noop instance |
Defined in Control.Monad.Class.MonadSTM.Internal Methods labelTVar :: TVar IO a -> String -> STM IO () Source # labelTMVar :: TMVar IO a -> String -> STM IO () Source # labelTQueue :: TQueue IO a -> String -> STM IO () Source # labelTBQueue :: TBQueue IO a -> String -> STM IO () Source # labelTArray :: (Ix i, Show i) => TArray IO i e -> String -> STM IO () Source # labelTSem :: TSem IO -> String -> STM IO () Source # labelTChan :: TChan IO a -> String -> STM IO () Source # labelTVarIO :: TVar IO a -> String -> IO () Source # labelTMVarIO :: TMVar IO a -> String -> IO () Source # labelTQueueIO :: TQueue IO a -> String -> IO () Source # labelTBQueueIO :: TBQueue IO a -> String -> IO () Source # labelTArrayIO :: (Ix i, Show i) => TArray IO i e -> String -> IO () Source # |
class MonadInspectSTM m => MonadTraceSTM m where Source #
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
Arguments
:: proxy m | |
-> TVar m a | |
-> (Maybe a -> a -> InspectMonad m TraceValue) | callback which receives initial value or |
-> STM m () |
Construct a trace output out of previous & new value of a TVar
. The
callback is called whenever an stm transaction which modifies the TVar
is
committed.
This is supported by IOSim
(and IOSimPOR
); IO
has a trivial instance.
The simplest example is:
traceTVar (Proxy @m) tvar (\_ -> TraceString . show)
Note that the interpretation of TraceValue
depends on the monad m
itself (see TraceValue
).
traceTMVar :: proxy m -> TMVar m a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad m TraceValue) -> STM m () Source #
default traceTMVar :: TMVar m a ~ TMVarDefault m a => proxy m -> TMVar m a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad m TraceValue) -> STM m () Source #
traceTQueue :: proxy m -> TQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> STM m () Source #
traceTBQueue :: proxy m -> TBQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> STM m () Source #
traceTSem :: proxy m -> TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> STM m () Source #
default traceTSem :: TSem m ~ TSemDefault m => proxy m -> TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> STM m () Source #
traceTVarIO :: TVar m a -> (Maybe a -> a -> InspectMonad m TraceValue) -> m () Source #
default traceTVarIO :: TVar m a -> (Maybe a -> a -> InspectMonad m TraceValue) -> m () Source #
traceTMVarIO :: TMVar m a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad m TraceValue) -> m () Source #
default traceTMVarIO :: TMVar m a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad m TraceValue) -> m () Source #
traceTQueueIO :: TQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> m () Source #
default traceTQueueIO :: TQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> m () Source #
traceTBQueueIO :: TBQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> m () Source #
default traceTBQueueIO :: TBQueue m a -> (Maybe [a] -> [a] -> InspectMonad m TraceValue) -> m () Source #
traceTSemIO :: TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> m () Source #
default traceTSemIO :: TSem m -> (Maybe Integer -> Integer -> InspectMonad m TraceValue) -> m () Source #
Instances
data TraceValue where Source #
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 IOSim
s dynamic tracing allows to
recover the value from the simulation trace (see
"Control.Monad.IOSim.selectTraceEventsDynamic").
Constructors
TraceValue | |
Fields
|
Bundled Patterns
pattern TraceDynamic :: () => forall tr. Typeable tr => tr -> TraceValue | Use only a dynamic tracer. |
pattern TraceString :: String -> TraceValue | Use only string tracing. |
pattern DontTrace :: TraceValue | Do not trace the value. |
class (MonadSTM m, Monad (InspectMonad m)) => MonadInspectSTM m where Source #
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 Source #
Methods
inspectTVar :: proxy m -> TVar m a -> InspectMonad m a Source #
Return the value of a TVar
as an InspectMonad
computation.
inspectTVar
is useful if the value of a TVar
observed by traceTVar
contains other TVar
s.
inspectTMVar :: proxy m -> TMVar m a -> InspectMonad m (Maybe a) Source #
Return the value of a MonadSTM
as an InspectMonad
computation.
Instances
MonadInspectSTM IO Source # | |
Defined in Control.Monad.Class.MonadSTM.Internal Methods inspectTVar :: proxy IO -> TVar IO a -> InspectMonad IO a Source # inspectTMVar :: proxy IO -> TMVar IO a -> InspectMonad IO (Maybe a) Source # |