Skip to content

Commit 8a2ef39

Browse files
ThreadStatus in IOSim and IOSimPOR
1 parent 83f53e4 commit 8a2ef39

File tree

8 files changed

+307
-88
lines changed

8 files changed

+307
-88
lines changed

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

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,5 +80,10 @@ instance Eq (TVar s a) where
8080
data SomeTVar s where
8181
SomeTVar :: !(TVar s a) -> SomeTVar s
8282

83-
data Deschedule = Yield | Interruptable | Blocked | Terminated | Sleep
83+
-- | The reason a thread finished running
84+
data FinishedReason = FinishedNormally
85+
| FinishedDied
86+
deriving (Ord, Eq, Show, Enum, Bounded)
87+
88+
data Deschedule = Yield | Interruptable | Blocked | Terminated FinishedReason | Sleep
8489
deriving Show

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

Lines changed: 40 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
{-# LANGUAGE RankNTypes #-}
1515
{-# LANGUAGE ScopedTypeVariables #-}
1616
{-# LANGUAGE TypeFamilies #-}
17+
{-# LANGUAGE RecordWildCards #-}
1718

1819
{-# OPTIONS_GHC -Wno-orphans #-}
1920
-- incomplete uni patterns in 'schedule' (when interpreting 'StmTxCommitted')
@@ -69,6 +70,7 @@ import Deque.Strict (Deque)
6970
import qualified Deque.Strict as Deque
7071

7172
import GHC.Exts (fromList)
73+
import GHC.Conc (ThreadStatus(..), BlockReason(..))
7274

7375
import Control.Exception (NonTermination (..), assert, throw)
7476
import Control.Monad (join)
@@ -122,14 +124,15 @@ labelledThreads threadMap =
122124
--
123125
data TimerVars s = TimerVars !(TVar s TimeoutState) !(TVar s Bool)
124126

125-
126127
-- | Internal state.
127128
--
128129
data SimState s a = SimState {
129130
runqueue :: !(Deque ThreadId),
130131
-- | All threads other than the currently running thread: both running
131132
-- and blocked threads.
132133
threads :: !(Map ThreadId (Thread s a)),
134+
-- | Keep track of the reason threads finished for 'threadStatus'
135+
finished :: !(Map ThreadId FinishedReason),
133136
-- | current time
134137
curTime :: !Time,
135138
-- | ordered list of timers
@@ -145,6 +148,7 @@ initialState =
145148
SimState {
146149
runqueue = mempty,
147150
threads = Map.empty,
151+
finished = Map.empty,
148152
curTime = Time 0,
149153
timers = PSQ.empty,
150154
clocks = Map.singleton (ClockId []) epoch1970,
@@ -189,6 +193,7 @@ schedule !thread@Thread{
189193
!simstate@SimState {
190194
runqueue,
191195
threads,
196+
finished,
192197
timers,
193198
clocks,
194199
nextVid, nextTmid,
@@ -207,9 +212,9 @@ schedule !thread@Thread{
207212

208213
ForkFrame -> do
209214
-- this thread is done
210-
!trace <- deschedule Terminated thread simstate
215+
!trace <- deschedule (Terminated FinishedNormally) thread simstate
211216
return $ SimTrace time tid tlbl EventThreadFinished
212-
$ SimTrace time tid tlbl (EventDeschedule Terminated)
217+
$ SimTrace time tid tlbl (EventDeschedule $ Terminated FinishedNormally)
213218
$ trace
214219

215220
MaskFrame k maskst' ctl' -> do
@@ -227,7 +232,7 @@ schedule !thread@Thread{
227232
let thread' = thread { threadControl = ThreadControl (k x) ctl' }
228233
schedule thread' simstate
229234

230-
Throw e -> {-# SCC "schedule.Throw" #-}
235+
Throw thrower e -> {-# SCC "schedule.Throw" #-}
231236
case unwindControlStack e thread of
232237
Right thread'@Thread { threadMasking = maskst' } -> do
233238
-- We found a suitable exception handler, continue with that
@@ -246,10 +251,12 @@ schedule !thread@Thread{
246251

247252
| otherwise -> do
248253
-- 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
250257
return $ SimTrace time tid tlbl (EventThrow e)
251258
$ SimTrace time tid tlbl (EventThreadUnhandled e)
252-
$ SimTrace time tid tlbl (EventDeschedule Terminated)
259+
$ SimTrace time tid tlbl (EventDeschedule $ Terminated reason)
253260
$ trace
254261

255262
Catch action' handler k ->
@@ -265,7 +272,7 @@ schedule !thread@Thread{
265272
case mbWHNF of
266273
Left e -> do
267274
-- 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 }
269276
schedule thread' simstate
270277
Right whnf -> do
271278
-- continue with the resulting WHNF
@@ -465,7 +472,7 @@ schedule !thread@Thread{
465472

466473
StmTxAborted _read e -> do
467474
-- 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 }
469476
!trace <- schedule thread' simstate
470477
return $ SimTrace time tid tlbl (EventTxAborted Nothing) trace
471478

@@ -494,6 +501,19 @@ schedule !thread@Thread{
494501
threads' = Map.adjust (\t -> t { threadLabel = Just l }) tid' threads
495502
schedule thread' simstate { threads = threads' }
496503

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+
497517
GetMaskState k ->
498518
{-# SCC "schedule.GetMaskState" #-} do
499519
let thread' = thread { threadControl = ThreadControl (k maskst) ctl }
@@ -518,7 +538,7 @@ schedule !thread@Thread{
518538
{-# SCC "schedule.ThrowTo" #-} do
519539
-- Throw to ourself is equivalent to a synchronous throw,
520540
-- 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 }
522542
trace <- schedule thread' simstate
523543
return (SimTrace time tid tlbl (EventThrowTo e tid) trace)
524544

@@ -548,8 +568,11 @@ schedule !thread@Thread{
548568
-- be resolved if the thread terminates or if it leaves the exception
549569
-- handler (when restoring the masking state would trigger the any
550570
-- 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'
553576
, threadBlocked = False
554577
}
555578
simstate'@SimState { threads = threads' }
@@ -618,7 +641,7 @@ deschedule Interruptable !thread@Thread {
618641
-- So immediately raise the exception and unblock the blocked thread
619642
-- if possible.
620643
{-# SCC "deschedule.Interruptable.Unmasked" #-}
621-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl
644+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl
622645
, threadMasking = MaskedInterruptible
623646
, threadThrowTo = etids }
624647
(unblocked,
@@ -653,13 +676,16 @@ deschedule Blocked !thread !simstate@SimState{threads} =
653676
threads' = Map.insert (threadId thread') thread' threads in
654677
reschedule simstate { threads = threads' }
655678

656-
deschedule Terminated !thread !simstate@SimState{ curTime = time, threads } =
679+
deschedule (Terminated reason) !thread !simstate@SimState{ curTime = time, threads } =
657680
-- This thread is done. If there are other threads blocked in a
658681
-- ThrowTo targeted at this thread then we can wake them up now.
659682
{-# SCC "deschedule.Terminated" #-}
660683
let !wakeup = map (l_labelled . snd) (reverse (threadThrowTo thread))
661684
(unblocked,
662-
!simstate') = unblockThreads wakeup simstate
685+
!simstate') = unblockThreads wakeup
686+
simstate { finished = Map.insert (threadId thread)
687+
reason
688+
(finished simstate) }
663689
in do
664690
!trace <- reschedule simstate'
665691
return $ traceMany

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

Lines changed: 11 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@ module Control.Monad.IOSim.Types
5959
, module Control.Monad.IOSim.CommonTypes
6060
, SimM
6161
, SimSTM
62+
, Thrower (..)
6263
) where
6364

6465
import Control.Applicative
@@ -112,6 +113,8 @@ import Control.Monad.IOSim.CommonTypes
112113
import Control.Monad.IOSim.STM
113114
import Control.Monad.IOSimPOR.Types
114115

116+
import GHC.Conc (ThreadStatus)
117+
115118

116119
import qualified System.IO.Error as IO.Error (userError)
117120

@@ -130,6 +133,8 @@ traceM x = IOSim $ oneShot $ \k -> Output (toDyn x) (k ())
130133
traceSTM :: Typeable a => a -> STMSim s ()
131134
traceSTM x = STM $ oneShot $ \k -> OutputStm (toDyn x) (k ())
132135

136+
data Thrower = ThrowSelf | ThrowOther deriving (Ord, Eq, Show)
137+
133138
data SimA s a where
134139
Return :: a -> SimA s a
135140

@@ -147,14 +152,15 @@ data SimA s a where
147152
UpdateTimeout:: Timeout (IOSim s) -> DiffTime -> SimA s b -> SimA s b
148153
CancelTimeout:: Timeout (IOSim s) -> SimA s b -> SimA s b
149154

150-
Throw :: SomeException -> SimA s a
155+
Throw :: Thrower -> SomeException -> SimA s a
151156
Catch :: Exception e =>
152157
SimA s a -> (e -> SimA s a) -> (a -> SimA s b) -> SimA s b
153158
Evaluate :: a -> (a -> SimA s b) -> SimA s b
154159

155160
Fork :: IOSim s () -> (ThreadId -> SimA s b) -> SimA s b
156161
GetThreadId :: (ThreadId -> SimA s b) -> SimA s b
157162
LabelThread :: ThreadId -> String -> SimA s b -> SimA s b
163+
ThreadStatus :: ThreadId -> (ThreadStatus -> SimA s b) -> SimA s b
158164

159165
Atomically :: STM s a -> (a -> SimA s b) -> SimA s b
160166

@@ -241,7 +247,7 @@ instance Monoid a => Monoid (IOSim s a) where
241247
#endif
242248

243249
instance Fail.MonadFail (IOSim s) where
244-
fail msg = IOSim $ oneShot $ \_ -> Throw (toException (IO.Error.userError msg))
250+
fail msg = IOSim $ oneShot $ \_ -> Throw ThrowSelf (toException (IO.Error.userError msg))
245251

246252
instance MonadFix (IOSim s) where
247253
mfix f = IOSim $ oneShot $ \k -> Fix f k
@@ -288,7 +294,7 @@ instance MonadSay (IOSim s) where
288294
say msg = IOSim $ oneShot $ \k -> Say msg (k ())
289295

290296
instance MonadThrow (IOSim s) where
291-
throwIO e = IOSim $ oneShot $ \_ -> Throw (toException e)
297+
throwIO e = IOSim $ oneShot $ \_ -> Throw ThrowSelf (toException e)
292298

293299
instance MonadEvaluate (IOSim s) where
294300
evaluate a = IOSim $ oneShot $ \k -> Evaluate a k
@@ -366,6 +372,7 @@ instance MonadThread (IOSim s) where
366372
type ThreadId (IOSim s) = ThreadId
367373
myThreadId = IOSim $ oneShot $ \k -> GetThreadId k
368374
labelThread t l = IOSim $ oneShot $ \k -> LabelThread t l (k ())
375+
threadStatus t = IOSim $ oneShot $ \k -> ThreadStatus t k
369376

370377
instance MonadFork (IOSim s) where
371378
forkIO task = IOSim $ oneShot $ \k -> Fork task k
@@ -799,6 +806,7 @@ data SimEventType
799806
| EventPerformAction StepId
800807
| EventReschedule ScheduleControl
801808
| EventUnblocked [ThreadId]
809+
| EventThreadStatus ThreadId ThreadId
802810
deriving Show
803811

804812
type TraceEvent = SimEventType

0 commit comments

Comments
 (0)