Skip to content

Commit 648d74d

Browse files
committed
Enhance documentation of MonadTraceSTM
Expose MonadTraceSTM methods from `Control.Monad.Class.MonadSTM`, otherwise the methods are only documented in the internal module `Control.Monad.Class.MonadSTM.Internal`!
1 parent 537aaed commit 648d74d

File tree

9 files changed

+69
-23
lines changed

9 files changed

+69
-23
lines changed

io-classes/src/Control/Concurrent/Class/MonadSTM.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
-- | This module corresponds to `Control.Concurrent.STM` in "stm" package
1+
-- | This module corresponds to "Control.Concurrent.STM" in "stm" package
22
--
33
module Control.Concurrent.Class.MonadSTM
44
(module STM)

io-classes/src/Control/Monad/Class/MonadSTM.hs

Lines changed: 13 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
-- | This module corresponds to `Control.Monad.STM` in "stm" package
1+
-- | This module corresponds to "Control.Monad.STM" in "stm" package
22
--
33
{-# LANGUAGE DataKinds #-}
44
{-# LANGUAGE DerivingStrategies #-}
@@ -14,10 +14,20 @@ module Control.Monad.Class.MonadSTM
1414
( MonadSTM (STM, atomically, retry, orElse, check)
1515
, throwSTM
1616
-- * non standard extensions
17+
--
18+
-- $non-standard-extensions
1719
, MonadLabelledSTM
18-
, MonadTraceSTM
19-
, MonadInspectSTM (..)
20+
, MonadTraceSTM (..)
2021
, TraceValue (..)
22+
, MonadInspectSTM (..)
2123
) where
2224

2325
import Control.Monad.Class.MonadSTM.Internal
26+
27+
-- $non-standard-extensions
28+
--
29+
-- The non standard extensions include `MonadLabelledSTM` and `MonadTraceSTM` /
30+
-- `MonadInspectSTM`. For `IO` these are all no-op, however they greatly
31+
-- enhance [`IOSim`](https://hackage.haskell.org/package/io-sim) capabilities.
32+
-- They are not only useful for debugging concurrency issues, but also to write
33+
-- testable properties.

io-classes/src/Control/Monad/Class/MonadSTM/Internal.hs

Lines changed: 45 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -76,18 +76,27 @@ import GHC.Stack
7676
import Numeric.Natural (Natural)
7777

7878

79-
-- The STM primitives
79+
-- | The STM primitives parametrised by a monad `m`.
80+
--
8081
class (Monad m, Monad (STM m)) => MonadSTM m where
81-
-- STM transactions
82+
-- | The STM monad.
8283
type STM m = (stm :: Type -> Type) | stm -> m
84+
-- | Atomically run an STM computation.
85+
--
86+
-- See `STM.atomically`.
8387
atomically :: HasCallStack => STM m a -> m a
8488

89+
-- | A type of a 'TVar'.
90+
--
91+
-- See `STM.TVar'.
8592
type TVar m :: Type -> Type
8693

8794
newTVar :: a -> STM m (TVar m a)
8895
readTVar :: TVar m a -> STM m a
8996
writeTVar :: TVar m a -> a -> STM m ()
97+
-- | See `STM.retry`.
9098
retry :: STM m a
99+
-- | See `STM.orElse`
91100
orElse :: STM m a -> STM m a -> STM m a
92101

93102
modifyTVar :: TVar m a -> (a -> a) -> STM m ()
@@ -103,6 +112,7 @@ class (Monad m, Monad (STM m)) => MonadSTM m where
103112
swapTVar :: TVar m a -> a -> STM m a
104113
swapTVar = swapTVarDefault
105114

115+
-- | See `STM.check`.
106116
check :: Bool -> STM m ()
107117
check True = return ()
108118
check _ = retry
@@ -384,10 +394,15 @@ swapTVarDefault var new = do
384394
return old
385395

386396

387-
-- | Labelled 'TVar's, 'TMVar's, 'TQueue's and 'TBQueue's.
397+
-- | Labelled `TVar`s & friends.
398+
--
399+
-- The `IO` instances is no-op, the `IOSim` instance enhances simulation trace.
400+
-- This is very useful when analysing low lever concurrency issues (e.g.
401+
-- deadlocks, livelocks etc).
388402
--
389403
class MonadSTM m
390404
=> MonadLabelledSTM m where
405+
-- | Name a `TVar`.
391406
labelTVar :: TVar m a -> String -> STM m ()
392407
labelTMVar :: TMVar m a -> String -> STM m ()
393408
labelTQueue :: TQueue m a -> String -> STM m ()
@@ -460,15 +475,21 @@ class MonadSTM m
460475
labelTChanIO = \v l -> atomically (labelTChan v l)
461476

462477

463-
-- | This type class is indented for 'io-sim', where one might want to access
464-
-- 'TVar' in the underlying 'ST' monad.
478+
-- | This type class is indented for
479+
-- ['io-sim'](https://hackage.haskell.org/package/io-sim), where one might want
480+
-- to access a 'TVar' in the underlying 'ST' monad.
465481
--
466482
class ( MonadSTM m
467483
, Monad (InspectMonad m)
468484
)
469485
=> MonadInspectSTM m where
470486
type InspectMonad m :: Type -> Type
487+
-- | Return the value of a `TVar` as an `InspectMonad` computation.
488+
--
489+
-- `inspectTVar` is useful if the value of a `TVar` observed by `traceTVar`
490+
-- contains other `TVar`s.
471491
inspectTVar :: proxy m -> TVar m a -> InspectMonad m a
492+
-- | Return the value of a `TMVar` as an `InspectMonad` computation.
472493
inspectTMVar :: proxy m -> TMVar m a -> InspectMonad m (Maybe a)
473494
-- TODO: inspectTQueue, inspectTBQueue
474495

@@ -480,8 +501,10 @@ instance MonadInspectSTM IO where
480501

481502

482503
-- | A GADT which instructs how to trace the value. The 'traceDynamic' will
483-
-- use dynamic tracing, e.g. 'Control.Monad.IOSim.traceM'; while 'traceString'
484-
-- will be traced with 'EventSay'.
504+
-- use dynamic tracing, e.g. "Control.Monad.IOSim.traceM"; while 'traceString'
505+
-- will be traced with 'EventSay'. The `IOSim`s dynamic tracing allows to
506+
-- recover the value from the simulation trace (see
507+
-- "Control.Monad.IOSim.selectTraceEventsDynamic").
485508
--
486509
data TraceValue where
487510
TraceValue :: forall tr. Typeable tr
@@ -491,7 +514,7 @@ data TraceValue where
491514
-> TraceValue
492515

493516

494-
-- | Use only dynamic tracer.
517+
-- | Use only a dynamic tracer.
495518
--
496519
pattern TraceDynamic :: () => forall tr. Typeable tr => tr -> TraceValue
497520
pattern TraceDynamic tr <- TraceValue { traceDynamic = Just tr }
@@ -520,14 +543,23 @@ pattern DontTrace <- TraceValue Nothing Nothing
520543
--
521544
class MonadInspectSTM m
522545
=> MonadTraceSTM m where
523-
-- | Construct a trace out of previous & new value of a 'TVar'. The callback
524-
-- is called whenever an stm transaction which modifies the 'TVar' is
546+
{-# MINIMAL traceTVar, traceTQueue, traceTBQueue #-}
547+
548+
-- | Construct a trace output out of previous & new value of a 'TVar'. The
549+
-- callback is called whenever an stm transaction which modifies the 'TVar' is
525550
-- committed.
526551
--
527-
-- This is supported by 'IOSim' and 'IOSimPOR'; 'IO' has a trivial instance.
552+
-- This is supported by 'IOSim' (and 'IOSimPOR'); 'IO' has a trivial instance.
553+
--
554+
-- The simplest example is:
555+
--
556+
-- >
557+
-- > traceTVar (Proxy @m) tvar (\_ -> TraceString . show)
558+
-- >
559+
--
560+
-- Note that the interpretation of `TraceValue` depends on the monad `m`
561+
-- itself (see 'TraceValue').
528562
--
529-
{-# MINIMAL traceTVar, traceTQueue, traceTBQueue #-}
530-
531563
traceTVar :: proxy m
532564
-> TVar m a
533565
-> (Maybe a -> a -> InspectMonad m TraceValue)

io-sim/src/Control/Monad/IOSim/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -143,7 +143,7 @@ runIOSim (IOSim k) = k Return
143143

144144
-- | 'IOSim' has the ability to story any 'Typeable' value in its trace which
145145
-- can then be recovered with `selectTraceEventsDynamic` or
146-
-- `selectTraceVentsDynamic'`.
146+
-- `selectTraceEventsDynamic'`.
147147
--
148148
traceM :: Typeable a => a -> IOSim s ()
149149
traceM x = IOSim $ oneShot $ \k -> Output (toDyn x) (k ())

strict-stm/src/Control/Concurrent/Class/MonadSTM/Strict.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,11 @@ module Control.Concurrent.Class.MonadSTM.Strict
44
(module STM)
55
where
66

7-
import Control.Monad.Class.MonadSTM as STM
7+
import Control.Monad.Class.MonadSTM as STM hiding ( traceTVar, traceTVarIO,
8+
traceTMVar, traceTMVarIO,
9+
traceTQueue, traceTQueueIO,
10+
traceTBQueue, traceTBQueueIO
11+
)
812
import Control.Concurrent.Class.MonadSTM.Strict.TVar as STM
913
import Control.Concurrent.Class.MonadSTM.Strict.TMVar as STM
1014
import Control.Concurrent.Class.MonadSTM.Strict.TChan as STM

strict-stm/src/Control/Concurrent/Class/MonadSTM/Strict/TBQueue.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ module Control.Concurrent.Class.MonadSTM.Strict.TBQueue
3535

3636

3737
import qualified Control.Concurrent.Class.MonadSTM.TBQueue as Lazy
38-
import Control.Monad.Class.MonadSTM
38+
import Control.Monad.Class.MonadSTM hiding (traceTBQueue, traceTBQueueIO)
3939

4040
import Numeric.Natural (Natural)
4141

strict-stm/src/Control/Concurrent/Class/MonadSTM/Strict/TMVar.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ module Control.Concurrent.Class.MonadSTM.Strict.TMVar
3838

3939

4040
import qualified Control.Concurrent.Class.MonadSTM.TMVar as Lazy
41-
import Control.Monad.Class.MonadSTM
41+
import Control.Monad.Class.MonadSTM hiding (traceTMVar, traceTMVarIO)
4242

4343

4444
type LazyTMVar m = Lazy.TMVar m

strict-stm/src/Control/Concurrent/Class/MonadSTM/Strict/TQueue.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ module Control.Concurrent.Class.MonadSTM.Strict.TQueue
3434

3535

3636
import qualified Control.Concurrent.Class.MonadSTM.TQueue as Lazy
37-
import Control.Monad.Class.MonadSTM
37+
import Control.Monad.Class.MonadSTM hiding (traceTQueue, traceTQueueIO)
3838

3939

4040
type LazyTQueue m = Lazy.TQueue m

strict-stm/src/Control/Concurrent/Class/MonadSTM/Strict/TVar.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ module Control.Concurrent.Class.MonadSTM.Strict.TVar
4040
) where
4141

4242
import qualified Control.Concurrent.Class.MonadSTM.TVar as Lazy
43-
import Control.Monad.Class.MonadSTM
43+
import Control.Monad.Class.MonadSTM hiding (traceTVar, traceTVarIO)
4444

4545
import GHC.Stack
4646

0 commit comments

Comments
 (0)