14
14
{-# LANGUAGE RankNTypes #-}
15
15
{-# LANGUAGE ScopedTypeVariables #-}
16
16
{-# LANGUAGE TypeFamilies #-}
17
+ {-# LANGUAGE RecordWildCards #-}
17
18
18
19
{-# OPTIONS_GHC -Wno-orphans #-}
19
20
-- incomplete uni patterns in 'schedule' (when interpreting 'StmTxCommitted')
@@ -69,6 +70,7 @@ import Deque.Strict (Deque)
69
70
import qualified Deque.Strict as Deque
70
71
71
72
import GHC.Exts (fromList )
73
+ import GHC.Conc (ThreadStatus (.. ), BlockReason (.. ))
72
74
73
75
import Control.Exception (NonTermination (.. ), assert , throw )
74
76
import Control.Monad (join )
@@ -122,14 +124,15 @@ labelledThreads threadMap =
122
124
--
123
125
data TimerVars s = TimerVars ! (TVar s TimeoutState ) ! (TVar s Bool )
124
126
125
-
126
127
-- | Internal state.
127
128
--
128
129
data SimState s a = SimState {
129
130
runqueue :: ! (Deque ThreadId ),
130
131
-- | All threads other than the currently running thread: both running
131
132
-- and blocked threads.
132
133
threads :: ! (Map ThreadId (Thread s a )),
134
+ -- | Keep track of the reason threads finished for 'threadStatus'
135
+ finished :: ! (Map ThreadId FinishedReason ),
133
136
-- | current time
134
137
curTime :: ! Time ,
135
138
-- | ordered list of timers
@@ -145,6 +148,7 @@ initialState =
145
148
SimState {
146
149
runqueue = mempty ,
147
150
threads = Map. empty,
151
+ finished = Map. empty,
148
152
curTime = Time 0 ,
149
153
timers = PSQ. empty,
150
154
clocks = Map. singleton (ClockId [] ) epoch1970,
@@ -189,6 +193,7 @@ schedule !thread@Thread{
189
193
! simstate@ SimState {
190
194
runqueue,
191
195
threads,
196
+ finished,
192
197
timers,
193
198
clocks,
194
199
nextVid, nextTmid,
@@ -207,9 +212,9 @@ schedule !thread@Thread{
207
212
208
213
ForkFrame -> do
209
214
-- this thread is done
210
- ! trace <- deschedule Terminated thread simstate
215
+ ! trace <- deschedule ( Terminated FinishedNormally ) thread simstate
211
216
return $ SimTrace time tid tlbl EventThreadFinished
212
- $ SimTrace time tid tlbl (EventDeschedule Terminated )
217
+ $ SimTrace time tid tlbl (EventDeschedule $ Terminated FinishedNormally )
213
218
$ trace
214
219
215
220
MaskFrame k maskst' ctl' -> do
@@ -227,7 +232,7 @@ schedule !thread@Thread{
227
232
let thread' = thread { threadControl = ThreadControl (k x) ctl' }
228
233
schedule thread' simstate
229
234
230
- Throw e -> {-# SCC "schedule.Throw" #-}
235
+ Throw thrower e -> {-# SCC "schedule.Throw" #-}
231
236
case unwindControlStack e thread of
232
237
Right thread'@ Thread { threadMasking = maskst' } -> do
233
238
-- We found a suitable exception handler, continue with that
@@ -246,10 +251,12 @@ schedule !thread@Thread{
246
251
247
252
| otherwise -> do
248
253
-- An unhandled exception in any other thread terminates the thread
249
- ! trace <- deschedule Terminated thread simstate
254
+ let reason | ThrowSelf <- thrower = FinishedNormally
255
+ | otherwise = FinishedDied
256
+ ! trace <- deschedule (Terminated reason) thread simstate
250
257
return $ SimTrace time tid tlbl (EventThrow e)
251
258
$ SimTrace time tid tlbl (EventThreadUnhandled e)
252
- $ SimTrace time tid tlbl (EventDeschedule Terminated )
259
+ $ SimTrace time tid tlbl (EventDeschedule $ Terminated reason )
253
260
$ trace
254
261
255
262
Catch action' handler k ->
@@ -265,7 +272,7 @@ schedule !thread@Thread{
265
272
case mbWHNF of
266
273
Left e -> do
267
274
-- schedule this thread to immediately raise the exception
268
- let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
275
+ let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
269
276
schedule thread' simstate
270
277
Right whnf -> do
271
278
-- continue with the resulting WHNF
@@ -465,7 +472,7 @@ schedule !thread@Thread{
465
472
466
473
StmTxAborted _read e -> do
467
474
-- schedule this thread to immediately raise the exception
468
- let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
475
+ let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
469
476
! trace <- schedule thread' simstate
470
477
return $ SimTrace time tid tlbl (EventTxAborted Nothing ) trace
471
478
@@ -494,6 +501,19 @@ schedule !thread@Thread{
494
501
threads' = Map. adjust (\ t -> t { threadLabel = Just l }) tid' threads
495
502
schedule thread' simstate { threads = threads' }
496
503
504
+ ThreadStatus tid' k ->
505
+ {-# SCC "schedule.ThreadStatus" #-} do
506
+ let result | Just r <- Map. lookup tid' finished = reasonToStatus r
507
+ | Just t <- Map. lookup tid' threads = threadStatus t
508
+ | otherwise = error " The impossible happened - tried to loookup thread in state."
509
+ reasonToStatus FinishedNormally = ThreadFinished
510
+ reasonToStatus FinishedDied = ThreadDied
511
+ threadStatus Thread {.. } | threadBlocked = ThreadBlocked BlockedOnOther
512
+ | otherwise = ThreadRunning
513
+
514
+ thread' = thread { threadControl = ThreadControl (k result) ctl }
515
+ schedule thread' simstate
516
+
497
517
GetMaskState k ->
498
518
{-# SCC "schedule.GetMaskState" #-} do
499
519
let thread' = thread { threadControl = ThreadControl (k maskst) ctl }
@@ -518,7 +538,7 @@ schedule !thread@Thread{
518
538
{-# SCC "schedule.ThrowTo" #-} do
519
539
-- Throw to ourself is equivalent to a synchronous throw,
520
540
-- and works irrespective of masking state since it does not block.
521
- let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
541
+ let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
522
542
trace <- schedule thread' simstate
523
543
return (SimTrace time tid tlbl (EventThrowTo e tid) trace)
524
544
@@ -548,8 +568,11 @@ schedule !thread@Thread{
548
568
-- be resolved if the thread terminates or if it leaves the exception
549
569
-- handler (when restoring the masking state would trigger the any
550
570
-- new pending async exception).
551
- let adjustTarget t@ Thread { threadControl = ThreadControl _ ctl' } =
552
- t { threadControl = ThreadControl (Throw e) ctl'
571
+ let thrower = case threadMasking <$> Map. lookup tid' threads of
572
+ Just Unmasked -> ThrowOther
573
+ _ -> ThrowSelf
574
+ adjustTarget t@ Thread { threadControl = ThreadControl _ ctl' } =
575
+ t { threadControl = ThreadControl (Throw thrower e) ctl'
553
576
, threadBlocked = False
554
577
}
555
578
simstate'@ SimState { threads = threads' }
@@ -618,7 +641,7 @@ deschedule Interruptable !thread@Thread {
618
641
-- So immediately raise the exception and unblock the blocked thread
619
642
-- if possible.
620
643
{-# SCC "deschedule.Interruptable.Unmasked" #-}
621
- let thread' = thread { threadControl = ThreadControl (Throw e) ctl
644
+ let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl
622
645
, threadMasking = MaskedInterruptible
623
646
, threadThrowTo = etids }
624
647
(unblocked,
@@ -653,13 +676,16 @@ deschedule Blocked !thread !simstate@SimState{threads} =
653
676
threads' = Map. insert (threadId thread') thread' threads in
654
677
reschedule simstate { threads = threads' }
655
678
656
- deschedule Terminated ! thread ! simstate@ SimState { curTime = time, threads } =
679
+ deschedule ( Terminated reason) ! thread ! simstate@ SimState { curTime = time, threads } =
657
680
-- This thread is done. If there are other threads blocked in a
658
681
-- ThrowTo targeted at this thread then we can wake them up now.
659
682
{-# SCC "deschedule.Terminated" #-}
660
683
let ! wakeup = map (l_labelled . snd ) (reverse (threadThrowTo thread))
661
684
(unblocked,
662
- ! simstate') = unblockThreads wakeup simstate
685
+ ! simstate') = unblockThreads wakeup
686
+ simstate { finished = Map. insert (threadId thread)
687
+ reason
688
+ (finished simstate) }
663
689
in do
664
690
! trace <- reschedule simstate'
665
691
return $ traceMany
0 commit comments