1 /* -----------------------------------------------------------------------------
3 * (c) The GHC Team, 1998-2012
5 * Code for starting, stopping and restarting threads.
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 * ---------------------------------------------------------------------------*/
16 * This module contains the two entry points and the final exit point
17 * to/from the Haskell world. We can enter either by:
19 * a) returning to the address on the top of the stack, or
20 * b) entering the closure on the top of the stack
22 * the function stg_stop_thread_entry is the final exit for a
23 * thread: it is the last return address on the stack. It returns
24 * to the scheduler marking the thread as finished.
27 #define CHECK_SENSIBLE_REGS() \
29 ASSERT(HpAlloc == 0); \
32 ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp);
34 /* -----------------------------------------------------------------------------
35 Returning from the STG world.
36 -------------------------------------------------------------------------- */
38 INFO_TABLE_RET(stg_stop_thread, STOP_FRAME,
40 PROF_HDR_FIELDS(W_,p1,p2))
41 /* no return list: explicit stack layout */
46 The top-top-level closures (e.g., "main") are of type "IO a".
47 When entered, they perform an IO action and return an 'a' in R1.
49 We save R1 on top of the stack where the scheduler can find it,
50 tidy up the registers and return to the scheduler.
52 We Leave the stack looking like this:
55 | -------------------> return value
60 The stg_enter_info is just a dummy info table so that the
61 garbage collector can understand the stack (there must always
62 be an info table on top of the stack).
66 Here we setup the stack unwinding annotation necessary to allow
67 debuggers to find their way back to the C stack.
69 This is a bit fiddly as we assume the layout of the stack prepared
70 for us by StgRun. Note that in most cases StgRun is written in assembler
71 and therefore has no associated unwind information. For this reason we
72 need to identify the platform stack pointer and return address values for
75 #if defined(x86_64_HOST_ARCH)
76 // offset of 8 in MachSp value due to return address
77 unwind MachSp = MachSp + RESERVED_C_STACK_BYTES + STG_RUN_STACK_FRAME_SIZE + 8,
78 UnwindReturnReg = W_[MachSp + RESERVED_C_STACK_BYTES + STG_RUN_STACK_FRAME_SIZE];
80 // FIXME: Fill in for other platforms
81 unwind MachSp = return,
82 UnwindReturnReg = return;
85 Sp = Sp + SIZEOF_StgStopFrame - WDS(2);
87 Sp(0) = stg_enter_info;
89 StgTSO_what_next(CurrentTSO) = ThreadComplete::I16;
93 /* The return code goes in BaseReg->rRet, and BaseReg is returned in R1 */
94 StgRegTable_rRet(BaseReg) = ThreadFinished;
100 /* -----------------------------------------------------------------------------
101 Start a thread from the scheduler by returning to the address on
102 the top of the stack. This is used for all entries to STG code
105 On the way back, we (usually) pass through stg_returnToSched which saves
106 the thread's state away nicely.
107 -------------------------------------------------------------------------- */
109 stg_returnToStackTop /* no args: explicit stack layout */
112 CHECK_SENSIBLE_REGS();
113 jump %ENTRY_CODE(Sp(0)) [];
116 stg_returnToSched /* no args: explicit stack layout */
119 r1 = R1; // foreign calls may clobber R1
121 foreign "C" threadPaused(MyCapability() "ptr", CurrentTSO);
126 // A variant of stg_returnToSched that doesn't call threadPaused() on the
127 // current thread. This is used for switching from compiled execution to the
128 // interpreter, where calling threadPaused() on every switch would be too
131 // See Note [avoiding threadPaused] in Interpreter.c
133 stg_returnToSchedNotPaused /* no args: explicit stack layout */
139 // A variant of stg_returnToSched, but instead of returning directly to the
140 // scheduler, we jump to the code fragment pointed to by R2. This lets us
141 // perform some final actions after making the thread safe, such as unlocking
142 // the MVar on which we are about to block in SMP mode.
143 stg_returnToSchedButFirst /* no args: explicit stack layout */
150 // foreign calls may clobber R1/R2/.., so we save them above
151 foreign "C" threadPaused(MyCapability() "ptr", CurrentTSO);
158 stg_threadFinished /* no args: explicit stack layout */
160 StgRegTable_rRet(BaseReg) = ThreadFinished;
165 /* -----------------------------------------------------------------------------
166 Strict IO application - performing an IO action and entering its result.
168 rts_evalIO() lets you perform Haskell IO actions from outside of
169 Haskell-land, returning back to you their result. Want this result
170 to be evaluated to WHNF by that time, so that we can easily get at
171 the int/char/whatever using the various get{Ty} functions provided
174 stg_forceIO takes care of this, performing the IO action and entering
175 the results that comes back.
177 ------------------------------------------------------------------------- */
179 INFO_TABLE_RET(stg_forceIO, RET_SMALL, P_ info_ptr)
185 /* Called when compiled with -falignment-sanitisation on alignment failure */
186 stg_badAlignment_entry