Skip to content

Commit 6d795fd

Browse files
committed
Attach label to TVars mentioned in Effects
1 parent 4c31d42 commit 6d795fd

File tree

5 files changed

+49
-34
lines changed

5 files changed

+49
-34
lines changed

io-sim/CHANGELOG.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33
## next version
44

55
- Support `threadLabel` (`io-classes-1.8`)
6+
- `IOSimPOR`'s `Effect` traces now will correctly show labels on read/written
7+
`TVars`.
68

79
## 1.6.0.0
810

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

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE DeriveAnyClass #-}
2+
{-# LANGUAGE DeriveFunctor #-}
23
{-# LANGUAGE DeriveGeneric #-}
34
{-# LANGUAGE DerivingStrategies #-}
45
{-# LANGUAGE DerivingVia #-}
@@ -25,9 +26,12 @@ module Control.Monad.IOSim.CommonTypes
2526
, TVarLabel
2627
, TVar (..)
2728
, SomeTVar (..)
29+
, someTVarToLabelled
2830
, Deschedule (..)
2931
, ThreadStatus (..)
3032
, BlockedReason (..)
33+
, Labelled (..)
34+
, ppLabelled
3135
-- * Utils
3236
, ppList
3337
) where
@@ -145,6 +149,11 @@ instance Eq (TVar s a) where
145149
data SomeTVar s where
146150
SomeTVar :: !(TVar s a) -> SomeTVar s
147151

152+
someTVarToLabelled :: SomeTVar s -> ST s (Labelled (SomeTVar s))
153+
someTVarToLabelled tv@(SomeTVar var) = do
154+
lbl <- readSTRef (tvarLabel var)
155+
pure (Labelled tv lbl)
156+
148157
data Deschedule = Yield
149158
| Interruptable
150159
| Blocked BlockedReason
@@ -162,6 +171,21 @@ data BlockedReason = BlockedOnSTM
162171
| BlockedOnThrowTo
163172
deriving (Eq, Show)
164173

174+
-- | A labelled value.
175+
--
176+
-- For example 'labelThread' or `labelTVar' will insert a label to `IOSimThreadId`
177+
-- (or `TVarId`).
178+
data Labelled a = Labelled {
179+
l_labelled :: !a,
180+
l_label :: !(Maybe String)
181+
}
182+
deriving (Eq, Ord, Generic, Functor)
183+
deriving Show via Quiet (Labelled a)
184+
185+
ppLabelled :: (a -> String) -> Labelled a -> String
186+
ppLabelled pp Labelled { l_labelled = a, l_label = Nothing } = pp a
187+
ppLabelled pp Labelled { l_labelled = a, l_label = Just lbl } = concat ["Labelled ", pp a, " ", lbl]
188+
165189
--
166190
-- Utils
167191
--

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

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,6 @@ module Control.Monad.IOSim.Types
5858
, ppTrace_
5959
, ppSimEvent
6060
, ppDebug
61-
, Labelled (..)
6261
, module Control.Monad.IOSim.CommonTypes
6362
, Thrower (..)
6463
, Time (..)
@@ -1207,21 +1206,6 @@ ppSimEventType = \case
12071206
ppEffect eff ]
12081207
EventRaces a -> show a
12091208

1210-
-- | A labelled value.
1211-
--
1212-
-- For example 'labelThread' or `labelTVar' will insert a label to `IOSimThreadId`
1213-
-- (or `TVarId`).
1214-
data Labelled a = Labelled {
1215-
l_labelled :: !a,
1216-
l_label :: !(Maybe String)
1217-
}
1218-
deriving (Eq, Ord, Generic)
1219-
deriving Show via Quiet (Labelled a)
1220-
1221-
ppLabelled :: (a -> String) -> Labelled a -> String
1222-
ppLabelled pp Labelled { l_labelled = a, l_label = Nothing } = pp a
1223-
ppLabelled pp Labelled { l_labelled = a, l_label = Just lbl } = concat ["Labelled ", pp a, " ", lbl]
1224-
12251209
--
12261210
-- Executing STM Transactions
12271211
--

io-sim/src/Control/Monad/IOSimPOR/Internal.hs

Lines changed: 12 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -568,10 +568,11 @@ schedule thread@Thread{
568568
CancelTimeout (Timeout tvar tmid) k -> do
569569
let timers' = PSQ.delete tmid timers
570570
written <- execAtomically' (runSTM $ writeTVar tvar TimeoutCancelled)
571+
written' <- mapM someTVarToLabelled written
571572
(wakeup, wokeby) <- threadsUnblockedByWrites written
572573
mapM_ (\(SomeTVar var) -> unblockAllThreadsFromTVar var) written
573574
let effect' = effect
574-
<> writeEffects written
575+
<> writeEffects written'
575576
<> wakeupEffects wakeup
576577
thread' = thread { threadControl = ThreadControl k ctl
577578
, threadEffect = effect'
@@ -636,10 +637,12 @@ schedule thread@Thread{
636637
(wakeup, wokeby) <- threadsUnblockedByWrites written
637638
mapM_ (\(SomeTVar tvar) -> unblockAllThreadsFromTVar tvar) written
638639
vClockRead <- leastUpperBoundTVarVClocks read
640+
read' <- mapM someTVarToLabelled read
641+
written' <- mapM someTVarToLabelled written
639642
let vClock' = vClock `leastUpperBoundVClock` vClockRead
640643
effect' = effect
641-
<> readEffects read
642-
<> writeEffects written
644+
<> readEffects read'
645+
<> writeEffects written'
643646
<> wakeupEffects unblocked
644647
thread' = thread { threadControl = ThreadControl (k x) ctl,
645648
threadVClock = vClock',
@@ -648,12 +651,12 @@ schedule thread@Thread{
648651
simstate') = unblockThreads True vClock' wakeup simstate
649652
sequence_ [ modifySTRef (tvarVClock r) (leastUpperBoundVClock vClock')
650653
| SomeTVar r <- created ++ written ]
651-
written' <- traverse (\(SomeTVar tvar) -> labelledTVarId tvar) written
654+
written'' <- traverse (\(SomeTVar tvar) -> labelledTVarId tvar) written
652655
created' <- traverse (\(SomeTVar tvar) -> labelledTVarId tvar) created
653656
-- We deschedule a thread after a transaction... another may have woken up.
654657
!trace <- deschedule Yield thread' simstate' { nextVid = nextVid' }
655658
return $
656-
SimPORTrace time tid tstep tlbl (EventTxCommitted written' created' (Just effect')) $
659+
SimPORTrace time tid tstep tlbl (EventTxCommitted written'' created' (Just effect')) $
657660
traceMany
658661
[ (time, tid', (-1), tlbl', EventTxWakeup vids')
659662
| tid' <- unblocked
@@ -674,7 +677,8 @@ schedule thread@Thread{
674677
StmTxAborted read e -> do
675678
-- schedule this thread to immediately raise the exception
676679
vClockRead <- leastUpperBoundTVarVClocks read
677-
let effect' = effect <> readEffects read
680+
read' <- mapM someTVarToLabelled read
681+
let effect' = effect <> readEffects read'
678682
thread' = thread { threadControl = ThreadControl (Throw e) ctl,
679683
threadVClock = vClock `leastUpperBoundVClock` vClockRead,
680684
threadEffect = effect' }
@@ -686,7 +690,8 @@ schedule thread@Thread{
686690
mapM_ (\(SomeTVar tvar) -> blockThreadOnTVar tid tvar) read
687691
vids <- traverse (\(SomeTVar tvar) -> labelledTVarId tvar) read
688692
vClockRead <- leastUpperBoundTVarVClocks read
689-
let effect' = effect <> readEffects read
693+
read' <- mapM someTVarToLabelled read
694+
let effect' = effect <> readEffects read'
690695
thread' = thread { threadVClock = vClock `leastUpperBoundVClock` vClockRead,
691696
threadEffect = effect' }
692697
!trace <- deschedule (Blocked BlockedOnSTM) thread' simstate

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

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -38,8 +38,8 @@ import Control.Monad.IOSim.CommonTypes
3838
-- execution step. Only used by *IOSimPOR*.
3939
--
4040
data Effect = Effect {
41-
effectReads :: !(Set TVarId),
42-
effectWrites :: !(Set TVarId),
41+
effectReads :: !(Set (Labelled TVarId)),
42+
effectWrites :: !(Set (Labelled TVarId)),
4343
effectForks :: !(Set IOSimThreadId),
4444
effectThrows :: ![IOSimThreadId],
4545
effectWakeup :: !(Set IOSimThreadId)
@@ -50,11 +50,11 @@ ppEffect :: Effect -> String
5050
ppEffect Effect { effectReads, effectWrites, effectForks, effectThrows, effectWakeup } =
5151
"Effect { " ++
5252
concat (List.intersperse ", " $
53-
[ "reads = " ++ show effectReads | not (null effectReads) ]
54-
++ [ "writes = " ++ show effectWrites | not (null effectWrites) ]
55-
++ [ "forks = " ++ ppList ppIOSimThreadId (Set.toList effectForks) | not (null effectForks) ]
56-
++ [ "throws = " ++ ppList ppIOSimThreadId effectThrows | not (null effectThrows) ]
57-
++ [ "wakeup = " ++ ppList ppIOSimThreadId (Set.toList effectWakeup) | not (null effectWakeup) ])
53+
[ "reads = " ++ ppList (ppLabelled show) (Set.toList effectReads) | not (null effectReads) ]
54+
++ [ "writes = " ++ ppList (ppLabelled show) (Set.toList effectWrites) | not (null effectWrites) ]
55+
++ [ "forks = " ++ ppList ppIOSimThreadId (Set.toList effectForks) | not (null effectForks) ]
56+
++ [ "throws = " ++ ppList ppIOSimThreadId effectThrows | not (null effectThrows) ]
57+
++ [ "wakeup = " ++ ppList ppIOSimThreadId (Set.toList effectWakeup) | not (null effectWakeup) ])
5858
++ " }"
5959

6060

@@ -72,14 +72,14 @@ instance Monoid Effect where
7272
-- readEffect :: SomeTVar s -> Effect
7373
-- readEffect r = mempty{effectReads = Set.singleton $ someTvarId r }
7474

75-
readEffects :: [SomeTVar s] -> Effect
76-
readEffects rs = mempty{effectReads = Set.fromList (map someTvarId rs)}
75+
readEffects :: [Labelled (SomeTVar s)] -> Effect
76+
readEffects rs = mempty{effectReads = Set.fromList (map (someTvarId <$>) rs)}
7777

7878
-- writeEffect :: SomeTVar s -> Effect
7979
-- writeEffect r = mempty{effectWrites = Set.singleton $ someTvarId r }
8080

81-
writeEffects :: [SomeTVar s] -> Effect
82-
writeEffects rs = mempty{effectWrites = Set.fromList (map someTvarId rs)}
81+
writeEffects :: [Labelled (SomeTVar s)] -> Effect
82+
writeEffects rs = mempty{effectWrites = Set.fromList (map (someTvarId <$>) rs)}
8383

8484
forkEffect :: IOSimThreadId -> Effect
8585
forkEffect tid = mempty{effectForks = Set.singleton tid}

0 commit comments

Comments
 (0)