Skip to content

Commit cc73e31

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

File tree

7 files changed

+397
-101
lines changed

7 files changed

+397
-101
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: 39 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,7 @@ import Deque.Strict (Deque)
6969
import qualified Deque.Strict as Deque
7070

7171
import GHC.Exts (fromList)
72+
import GHC.Conc (ThreadStatus(..), BlockReason(..))
7273

7374
import Control.Exception (NonTermination (..), assert, throw)
7475
import Control.Monad (join)
@@ -122,14 +123,15 @@ labelledThreads threadMap =
122123
--
123124
data TimerVars s = TimerVars !(TVar s TimeoutState) !(TVar s Bool)
124125

125-
126126
-- | Internal state.
127127
--
128128
data SimState s a = SimState {
129129
runqueue :: !(Deque ThreadId),
130130
-- | All threads other than the currently running thread: both running
131131
-- and blocked threads.
132132
threads :: !(Map ThreadId (Thread s a)),
133+
-- | Keep track of the reason threads finished for 'threadStatus'
134+
finished :: !(Map ThreadId FinishedReason),
133135
-- | current time
134136
curTime :: !Time,
135137
-- | ordered list of timers
@@ -145,6 +147,7 @@ initialState =
145147
SimState {
146148
runqueue = mempty,
147149
threads = Map.empty,
150+
finished = Map.empty,
148151
curTime = Time 0,
149152
timers = PSQ.empty,
150153
clocks = Map.singleton (ClockId []) epoch1970,
@@ -189,6 +192,7 @@ schedule !thread@Thread{
189192
!simstate@SimState {
190193
runqueue,
191194
threads,
195+
finished,
192196
timers,
193197
clocks,
194198
nextVid, nextTmid,
@@ -207,9 +211,9 @@ schedule !thread@Thread{
207211

208212
ForkFrame -> do
209213
-- this thread is done
210-
!trace <- deschedule Terminated thread simstate
214+
!trace <- deschedule (Terminated FinishedNormally) thread simstate
211215
return $ SimTrace time tid tlbl EventThreadFinished
212-
$ SimTrace time tid tlbl (EventDeschedule Terminated)
216+
$ SimTrace time tid tlbl (EventDeschedule $ Terminated FinishedNormally)
213217
$ trace
214218

215219
MaskFrame k maskst' ctl' -> do
@@ -227,7 +231,7 @@ schedule !thread@Thread{
227231
let thread' = thread { threadControl = ThreadControl (k x) ctl' }
228232
schedule thread' simstate
229233

230-
Throw e -> {-# SCC "schedule.Throw" #-}
234+
Throw thrower e -> {-# SCC "schedule.Throw" #-}
231235
case unwindControlStack e thread of
232236
Right thread'@Thread { threadMasking = maskst' } -> do
233237
-- We found a suitable exception handler, continue with that
@@ -246,10 +250,12 @@ schedule !thread@Thread{
246250

247251
| otherwise -> do
248252
-- An unhandled exception in any other thread terminates the thread
249-
!trace <- deschedule Terminated thread simstate
253+
let reason | ThrowSelf <- thrower = FinishedNormally
254+
| otherwise = FinishedDied
255+
!trace <- deschedule (Terminated reason) thread simstate
250256
return $ SimTrace time tid tlbl (EventThrow e)
251257
$ SimTrace time tid tlbl (EventThreadUnhandled e)
252-
$ SimTrace time tid tlbl (EventDeschedule Terminated)
258+
$ SimTrace time tid tlbl (EventDeschedule $ Terminated reason)
253259
$ trace
254260

255261
Catch action' handler k ->
@@ -265,7 +271,7 @@ schedule !thread@Thread{
265271
case mbWHNF of
266272
Left e -> do
267273
-- schedule this thread to immediately raise the exception
268-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
274+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
269275
schedule thread' simstate
270276
Right whnf -> do
271277
-- continue with the resulting WHNF
@@ -465,7 +471,7 @@ schedule !thread@Thread{
465471

466472
StmTxAborted _read e -> do
467473
-- schedule this thread to immediately raise the exception
468-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
474+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
469475
!trace <- schedule thread' simstate
470476
return $ SimTrace time tid tlbl (EventTxAborted Nothing) trace
471477

@@ -494,6 +500,19 @@ schedule !thread@Thread{
494500
threads' = Map.adjust (\t -> t { threadLabel = Just l }) tid' threads
495501
schedule thread' simstate { threads = threads' }
496502

503+
ThreadStatus tid' k ->
504+
{-# SCC "schedule.ThreadStatus" #-} do
505+
let result | Just r <- Map.lookup tid' finished = reasonToStatus r
506+
| Just t <- Map.lookup tid' threads = threadStatus t
507+
| otherwise = error "The impossible happened - tried to loookup thread in state."
508+
reasonToStatus FinishedNormally = ThreadFinished
509+
reasonToStatus FinishedDied = ThreadDied
510+
threadStatus t | threadBlocked t = ThreadBlocked BlockedOnOther
511+
| otherwise = ThreadRunning
512+
513+
thread' = thread { threadControl = ThreadControl (k result) ctl }
514+
schedule thread' simstate
515+
497516
GetMaskState k ->
498517
{-# SCC "schedule.GetMaskState" #-} do
499518
let thread' = thread { threadControl = ThreadControl (k maskst) ctl }
@@ -518,7 +537,7 @@ schedule !thread@Thread{
518537
{-# SCC "schedule.ThrowTo" #-} do
519538
-- Throw to ourself is equivalent to a synchronous throw,
520539
-- and works irrespective of masking state since it does not block.
521-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
540+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
522541
trace <- schedule thread' simstate
523542
return (SimTrace time tid tlbl (EventThrowTo e tid) trace)
524543

@@ -548,8 +567,11 @@ schedule !thread@Thread{
548567
-- be resolved if the thread terminates or if it leaves the exception
549568
-- handler (when restoring the masking state would trigger the any
550569
-- new pending async exception).
551-
let adjustTarget t@Thread{ threadControl = ThreadControl _ ctl' } =
552-
t { threadControl = ThreadControl (Throw e) ctl'
570+
let thrower = case threadMasking <$> Map.lookup tid' threads of
571+
Just Unmasked -> ThrowOther
572+
_ -> ThrowSelf
573+
adjustTarget t@Thread{ threadControl = ThreadControl _ ctl' } =
574+
t { threadControl = ThreadControl (Throw thrower e) ctl'
553575
, threadBlocked = False
554576
}
555577
simstate'@SimState { threads = threads' }
@@ -618,7 +640,7 @@ deschedule Interruptable !thread@Thread {
618640
-- So immediately raise the exception and unblock the blocked thread
619641
-- if possible.
620642
{-# SCC "deschedule.Interruptable.Unmasked" #-}
621-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl
643+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl
622644
, threadMasking = MaskedInterruptible
623645
, threadThrowTo = etids }
624646
(unblocked,
@@ -653,13 +675,16 @@ deschedule Blocked !thread !simstate@SimState{threads} =
653675
threads' = Map.insert (threadId thread') thread' threads in
654676
reschedule simstate { threads = threads' }
655677

656-
deschedule Terminated !thread !simstate@SimState{ curTime = time, threads } =
678+
deschedule (Terminated reason) !thread !simstate@SimState{ curTime = time, threads } =
657679
-- This thread is done. If there are other threads blocked in a
658680
-- ThrowTo targeted at this thread then we can wake them up now.
659681
{-# SCC "deschedule.Terminated" #-}
660682
let !wakeup = map (l_labelled . snd) (reverse (threadThrowTo thread))
661683
(unblocked,
662-
!simstate') = unblockThreads wakeup simstate
684+
!simstate') = unblockThreads wakeup
685+
simstate { finished = Map.insert (threadId thread)
686+
reason
687+
(finished simstate) }
663688
in do
664689
!trace <- reschedule simstate'
665690
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)