1 /* -----------------------------------------------------------------------------
3 * (c) The GHC Team, 1998-2004
7 * This file is written in a subset of C--, extended with various
8 * features specific to GHC. It is compiled by GHC directly. For the
9 * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
11 * ---------------------------------------------------------------------------*/
14 #include "RaiseAsync.h"
16 import CLOSURE ghczmprim_GHCziTypes_True_closure;
18 /* -----------------------------------------------------------------------------
21 A thread can request that asynchronous exceptions not be delivered
22 ("masked") for the duration of an I/O computation. The primitives
24 maskAsyncExceptions# :: IO a -> IO a
28 maskUninterruptible# :: IO a -> IO a
30 are used for this purpose. During a masked section, asynchronous
31 exceptions may be unmasked again temporarily:
33 unmaskAsyncExceptions# :: IO a -> IO a
35 Furthermore, asynchronous exceptions are masked automatically during
36 the execution of an exception handler. All three of these primitives
37 leave a continuation on the stack which reverts to the previous
38 state (masked interruptible, masked non-interruptible, or unmasked)
41 A thread which wants to raise an exception in another thread (using
42 killThread#) must block until the target thread is ready to receive
43 it. The action of unmasking exceptions in a thread will release all
44 the threads waiting to deliver exceptions to that thread.
46 NB. there's a bug in here. If a thread is inside an
47 unsafePerformIO, and inside maskAsyncExceptions# (there is an
48 unmaskAsyncExceptions_ret on the stack), and it is blocked in an
49 interruptible operation, and it receives an exception, then the
50 unsafePerformIO thunk will be updated with a stack object
51 containing the unmaskAsyncExceptions_ret frame. Later, when
52 someone else evaluates this thunk, the original masking state is
55 -------------------------------------------------------------------------- */
58 INFO_TABLE_RET(stg_unmaskAsyncExceptionszh_ret, RET_SMALL, W_ info_ptr)
61 unwind Sp = Sp + WDS(1);
67 StgTSO_flags(CurrentTSO) = %lobits32(
68 TO_W_(StgTSO_flags(CurrentTSO)) & ~(TSO_BLOCKEX|TSO_INTERRUPTIBLE));
70 /* Eagerly raise a masked exception, if there is one */
71 if (StgTSO_blocked_exceptions(CurrentTSO) != END_TSO_QUEUE) {
73 STK_CHK_P_LL (WDS(2), stg_unmaskAsyncExceptionszh_ret_info, R1);
75 * We have to be very careful here, as in killThread#, since
76 * we are about to raise an async exception in the current
77 * thread, which might result in the thread being killed.
81 Sp(0) = stg_ret_p_info;
83 (r) = ccall maybePerformBlockedException (MyCapability() "ptr",
86 if (StgTSO_what_next(CurrentTSO) == ThreadKilled::I16) {
87 jump stg_threadFinished [];
90 ASSERT(StgTSO_what_next(CurrentTSO) == ThreadRunGHC::I16);
92 jump %ENTRY_CODE(Sp(0)) [R1];
97 the thread might have been removed from the
98 blocked_exception list by someone else in the meantime.
99 Just restore the stack pointer and continue.
107 jump %ENTRY_CODE(Sp(0)) [R1];
110 INFO_TABLE_RET(stg_maskAsyncExceptionszh_ret, RET_SMALL, W_ info_ptr)
113 StgTSO_flags(CurrentTSO) =
115 TO_W_(StgTSO_flags(CurrentTSO))
116 | TSO_BLOCKEX | TSO_INTERRUPTIBLE
122 INFO_TABLE_RET(stg_maskUninterruptiblezh_ret, RET_SMALL, W_ info_ptr)
125 StgTSO_flags(CurrentTSO) =
127 (TO_W_(StgTSO_flags(CurrentTSO))
135 stg_maskAsyncExceptionszh /* explicit stack */
137 /* Args: R1 :: IO a */
138 STK_CHK_P_LL (WDS(1)/* worst case */, stg_maskAsyncExceptionszh, R1);
140 if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_BLOCKEX) == 0) {
141 /* avoid growing the stack unnecessarily */
142 if (Sp(0) == stg_maskAsyncExceptionszh_ret_info) {
146 Sp(0) = stg_unmaskAsyncExceptionszh_ret_info;
149 if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_INTERRUPTIBLE) == 0) {
151 Sp(0) = stg_maskUninterruptiblezh_ret_info;
155 StgTSO_flags(CurrentTSO) = %lobits32(
156 TO_W_(StgTSO_flags(CurrentTSO)) | TSO_BLOCKEX | TSO_INTERRUPTIBLE);
159 TICK_SLOW_CALL_fast_v();
160 jump stg_ap_v_fast [R1];
163 stg_maskUninterruptiblezh /* explicit stack */
165 /* Args: R1 :: IO a */
166 STK_CHK_P_LL (WDS(1)/* worst case */, stg_maskUninterruptiblezh, R1);
168 if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_BLOCKEX) == 0) {
169 /* avoid growing the stack unnecessarily */
170 if (Sp(0) == stg_maskUninterruptiblezh_ret_info) {
174 Sp(0) = stg_unmaskAsyncExceptionszh_ret_info;
177 if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_INTERRUPTIBLE) != 0) {
179 Sp(0) = stg_maskAsyncExceptionszh_ret_info;
183 StgTSO_flags(CurrentTSO) = %lobits32(
184 (TO_W_(StgTSO_flags(CurrentTSO)) | TSO_BLOCKEX) & ~TSO_INTERRUPTIBLE);
187 TICK_SLOW_CALL_fast_v();
188 jump stg_ap_v_fast [R1];
191 stg_unmaskAsyncExceptionszh /* explicit stack */
196 /* Args: R1 :: IO a */
200 STK_CHK_P_LL (WDS(4), stg_unmaskAsyncExceptionszh, io);
201 /* 4 words: one for the unmask frame, 3 for setting up the
202 * stack to call maybePerformBlockedException() below.
205 /* If exceptions are already unmasked, there's nothing to do */
206 if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_BLOCKEX) != 0) {
208 /* avoid growing the stack unnecessarily */
209 if (Sp(0) == stg_unmaskAsyncExceptionszh_ret_info) {
213 if ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_INTERRUPTIBLE) != 0) {
214 Sp(0) = stg_maskAsyncExceptionszh_ret_info;
216 Sp(0) = stg_maskUninterruptiblezh_ret_info;
220 StgTSO_flags(CurrentTSO) = %lobits32(
221 TO_W_(StgTSO_flags(CurrentTSO)) & ~(TSO_BLOCKEX|TSO_INTERRUPTIBLE));
223 /* Eagerly raise a masked exception, if there is one */
224 if (StgTSO_blocked_exceptions(CurrentTSO) != END_TSO_QUEUE) {
226 * We have to be very careful here, as in killThread#, since
227 * we are about to raise an async exception in the current
228 * thread, which might result in the thread being killed.
230 * Now, if we are to raise an exception in the current
231 * thread, there might be an update frame above us on the
232 * stack due to unsafePerformIO. Hence, the stack must
233 * make sense, because it is about to be snapshotted into
237 Sp(2) = stg_ap_v_info;
239 Sp(0) = stg_enter_info;
242 (r) = ccall maybePerformBlockedException (MyCapability() "ptr",
246 if (StgTSO_what_next(CurrentTSO) == ThreadKilled::I16) {
247 jump stg_threadFinished [];
250 ASSERT(StgTSO_what_next(CurrentTSO) == ThreadRunGHC::I16);
252 jump %ENTRY_CODE(Sp(0)) [R1];
255 /* we'll just call R1 directly, below */
262 TICK_SLOW_CALL_fast_v();
264 jump stg_ap_v_fast [R1];
268 stg_getMaskingStatezh ()
272 returns: 0 == unmasked,
273 1 == masked, non-interruptible,
274 2 == masked, interruptible
276 return (((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_BLOCKEX) != 0) +
277 ((TO_W_(StgTSO_flags(CurrentTSO)) & TSO_INTERRUPTIBLE) != 0));
280 stg_killThreadzh (P_ target, P_ exception)
284 /* Needs 3 words because throwToSingleThreaded uses some stack */
285 STK_CHK_PP (WDS(3), stg_killThreadzh, target, exception);
286 /* We call allocate in throwTo(), so better check for GC */
287 MAYBE_GC_PP (stg_killThreadzh, target, exception);
290 * We might have killed ourselves. In which case, better be *very*
291 * careful. If the exception killed us, then return to the scheduler.
292 * If the exception went to a catch frame, we'll just continue from
295 if (target == CurrentTSO) {
297 * So what should happen if a thread calls "throwTo self" inside
298 * unsafePerformIO, and later the closure is evaluated by another
299 * thread? Presumably it should behave as if throwTo just returned,
300 * and then continue from there. See #3279, #3288. This is what
301 * happens: on resumption, we will just jump to the next frame on
302 * the stack, which is the return point for stg_killThreadzh.
306 jump stg_killMyself [R1,R2];
310 (msg) = ccall throwTo(MyCapability() "ptr",
318 StgTSO_why_blocked(CurrentTSO) = BlockedOnMsgThrowTo;
319 StgTSO_block_info(CurrentTSO) = msg;
320 // we must block, and unlock the message before returning
321 jump stg_block_throwto (target, exception);
327 * We must switch into low-level Cmm in order to raise an exception in
328 * the current thread, hence this is in a separate proc with arguments
329 * passed explicitly in R1 and R2.
333 P_ target, exception;
338 /* ToDo: what if the current thread is masking exceptions? */
339 ccall throwToSingleThreaded(MyCapability() "ptr",
340 target "ptr", exception "ptr");
341 if (StgTSO_what_next(CurrentTSO) == ThreadKilled::I16) {
342 jump stg_threadFinished [];
345 ASSERT(StgTSO_what_next(CurrentTSO) == ThreadRunGHC::I16);
346 jump %ENTRY_CODE(Sp(0)) [];
350 /* -----------------------------------------------------------------------------
352 -------------------------------------------------------------------------- */
354 /* Catch frames are very similar to update frames, but when entering
355 * one we just pop the frame off the stack and perform the correct
356 * kind of return to the activation record underneath us on the stack.
359 #define CATCH_FRAME_FIELDS(w_,p_,info_ptr,p1,p2,exceptions_blocked,handler) \
361 PROF_HDR_FIELDS(w_,p1,p2) \
362 w_ exceptions_blocked, \
366 INFO_TABLE_RET(stg_catch_frame, CATCH_FRAME,
367 CATCH_FRAME_FIELDS(W_,P_,info_ptr, p1, p2,
368 exceptions_blocked,handler))
374 /* -----------------------------------------------------------------------------
375 * The catch infotable
377 * This should be exactly the same as would be generated by this STG code
379 * catch = {x,h} \n {} -> catch#{x,h}
381 * It is used in deleteThread when reverting blackholes.
382 * -------------------------------------------------------------------------- */
384 INFO_TABLE(stg_catch,2,0,FUN,"catch","catch")
387 jump stg_catchzh(StgClosure_payload(node,0),StgClosure_payload(node,1));
390 stg_catchzh ( P_ io, /* :: IO a */
391 P_ handler /* :: Exception -> IO a */ )
393 W_ exceptions_blocked;
398 TO_W_(StgTSO_flags(CurrentTSO)) & (TSO_BLOCKEX | TSO_INTERRUPTIBLE);
399 TICK_CATCHF_PUSHED();
401 /* Apply R1 to the realworld token */
403 TICK_SLOW_CALL_fast_v();
406 (CATCH_FRAME_FIELDS(,,stg_catch_frame_info, CCCS, 0,
407 exceptions_blocked, handler))
411 /* -----------------------------------------------------------------------------
412 * The raise infotable
414 * This should be exactly the same as would be generated by this STG code
416 * raise = {err} \n {} -> raise#{err}
418 * It is used in stg_raisezh to update thunks on the update list
419 * -------------------------------------------------------------------------- */
421 INFO_TABLE(stg_raise,1,0,THUNK_1_0,"raise","raise")
423 jump stg_raisezh(StgThunk_payload(R1,0));
427 no_break_on_exception: W_[1];
430 INFO_TABLE_RET(stg_raise_ret, RET_SMALL, W_ info_ptr, P_ exception)
433 W_[no_break_on_exception] = 1;
434 jump stg_raisezh (exception);
437 stg_raisezh /* explicit stack */
439 * args : R1 :: Exception
441 * Here we assume that the NativeNodeCall convention always puts the
442 * first argument in R1 (which it does). We cannot use high-level cmm
443 * due to all the LOAD_THREAD_STATE()/SAVE_THREAD_STATE() and stack
444 * walking that happens in here.
453 #if defined(PROFILING)
454 /* Debugging tool: on raising an exception, show where we are. */
456 /* ToDo: currently this is a hack. Would be much better if
457 * the info was only displayed for an *uncaught* exception.
459 if (RtsFlags_ProfFlags_showCCSOnException(RtsFlags) != 0::I32) {
461 ccall fprintCCS_stderr(CCCS "ptr",
470 (frame_type) = ccall raiseExceptionHelper(BaseReg "ptr", CurrentTSO "ptr", exception "ptr");
472 if (frame_type == ATOMICALLY_FRAME) {
473 /* The exception has reached the edge of a memory transaction. Check that
474 * the transaction is valid. If not then perhaps the exception should
475 * not have been thrown: re-run the transaction. "trec" will either be
476 * a top-level transaction running the atomic block, or a nested
477 * transaction running an invariant check. In the latter case we
478 * abort and de-allocate the top-level transaction that encloses it
479 * as well (we could just abandon its transaction record, but this makes
480 * sure it's marked as aborted and available for re-use). */
483 trec = StgTSO_trec(CurrentTSO);
484 (r) = ccall stmValidateNestOfTransactions(MyCapability() "ptr", trec "ptr");
485 outer = StgTRecHeader_enclosing_trec(trec);
486 ccall stmAbortTransaction(MyCapability() "ptr", trec "ptr");
487 ccall stmFreeAbortedTRec(MyCapability() "ptr", trec "ptr");
489 if (outer != NO_TREC) {
490 ccall stmAbortTransaction(MyCapability() "ptr", outer "ptr");
491 ccall stmFreeAbortedTRec(MyCapability() "ptr", outer "ptr");
494 StgTSO_trec(CurrentTSO) = NO_TREC;
496 // Transaction was valid: continue searching for a catch frame
497 Sp = Sp + SIZEOF_StgAtomicallyFrame;
498 goto retry_pop_stack;
500 // Transaction was not valid: we retry the exception (otherwise continue
501 // with a further call to raiseExceptionHelper)
502 ("ptr" trec) = ccall stmStartTransaction(MyCapability() "ptr", NO_TREC "ptr");
503 StgTSO_trec(CurrentTSO) = trec;
504 R1 = StgAtomicallyFrame_code(Sp);
505 jump stg_ap_v_fast [R1];
509 // After stripping the stack, see whether we should break here for
510 // GHCi (c.f. the -fbreak-on-exception flag). We do this after
511 // stripping the stack for a reason: we'll be inspecting values in
512 // GHCi, and it helps if all the thunks under evaluation have
513 // already been updated with the exception, rather than being left
515 if (W_[no_break_on_exception] != 0) {
516 W_[no_break_on_exception] = 0;
518 if (TO_W_(CInt[rts_stop_on_exception]) != 0) {
520 // we don't want any further exceptions to be caught,
521 // until GHCi is ready to handle them. This prevents
522 // deadlock if an exception is raised in InteractiveUI,
523 // for exmplae. Perhaps the stop_on_exception flag should
525 CInt[rts_stop_on_exception] = 0;
526 ("ptr" ioAction) = ccall deRefStablePtr (W_[rts_breakpoint_io_action] "ptr");
529 Sp(4) = stg_raise_ret_info;
530 Sp(3) = exception; // the AP_STACK
531 Sp(2) = ghczmprim_GHCziTypes_True_closure; // dummy breakpoint info
532 Sp(1) = ghczmprim_GHCziTypes_True_closure; // True <=> a breakpoint
534 jump RET_LBL(stg_ap_pppv) [R1];
538 if (frame_type == STOP_FRAME) {
540 * We've stripped the entire stack, the thread is now dead.
541 * We will leave the stack in a GC'able state, see the stg_stop_thread
542 * entry code in StgStartup.cmm.
545 stack = StgTSO_stackobj(CurrentTSO);
546 Sp = stack + OFFSET_StgStack_stack
547 + WDS(TO_W_(StgStack_stack_size(stack))) - WDS(2);
548 Sp(1) = exception; /* save the exception */
549 Sp(0) = stg_enter_info; /* so that GC can traverse this stack */
550 StgTSO_what_next(CurrentTSO) = ThreadKilled::I16;
551 SAVE_THREAD_STATE(); /* inline! */
553 jump stg_threadFinished [];
556 /* Ok, Sp points to the enclosing CATCH_FRAME or CATCH_STM_FRAME.
557 * Pop everything down to and including this frame, update Su,
558 * push R1, and enter the handler.
560 if (frame_type == CATCH_FRAME) {
561 handler = StgCatchFrame_handler(Sp);
563 handler = StgCatchSTMFrame_handler(Sp);
566 /* Restore the masked/unmasked state for asynchronous exceptions
567 * at the CATCH_FRAME.
569 * If exceptions were unmasked, arrange that they are unmasked
570 * again after executing the handler by pushing an
571 * unmaskAsyncExceptions_ret stack frame.
573 * If we've reached an STM catch frame then roll back the nested
574 * transaction we were using.
578 if (frame_type == CATCH_FRAME)
580 Sp = Sp + SIZEOF_StgCatchFrame;
581 if ((StgCatchFrame_exceptions_blocked(frame) & TSO_BLOCKEX) == 0) {
583 Sp(0) = stg_unmaskAsyncExceptionszh_ret_info;
586 /* Ensure that async exceptions are masked when running the handler.
588 StgTSO_flags(CurrentTSO) = %lobits32(
589 TO_W_(StgTSO_flags(CurrentTSO)) | TSO_BLOCKEX | TSO_INTERRUPTIBLE);
591 /* The interruptible state is inherited from the context of the
592 * catch frame, but note that TSO_INTERRUPTIBLE is only meaningful
593 * if TSO_BLOCKEX is set. (we got this wrong earlier, and #4988
594 * was a symptom of the bug).
596 if ((StgCatchFrame_exceptions_blocked(frame) &
597 (TSO_BLOCKEX | TSO_INTERRUPTIBLE)) == TSO_BLOCKEX) {
598 StgTSO_flags(CurrentTSO) = %lobits32(
599 TO_W_(StgTSO_flags(CurrentTSO)) & ~TSO_INTERRUPTIBLE);
602 else /* CATCH_STM_FRAME */
605 trec = StgTSO_trec(CurrentTSO);
606 outer = StgTRecHeader_enclosing_trec(trec);
607 ccall stmAbortTransaction(MyCapability() "ptr", trec "ptr");
608 ccall stmFreeAbortedTRec(MyCapability() "ptr", trec "ptr");
609 StgTSO_trec(CurrentTSO) = outer;
610 Sp = Sp + SIZEOF_StgCatchSTMFrame;
613 /* Call the handler, passing the exception value and a realworld
614 * token as arguments.
621 TICK_SLOW_CALL_fast_pv();
622 jump RET_LBL(stg_ap_pv) [R1];
625 stg_raiseIOzh (P_ exception)
627 jump stg_raisezh (exception);