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