/* -----------------------------------------------------------------------------
*
- * (c) The GHC Team, 1998-2004
+ * (c) The GHC Team, 1998-2012
*
* Code for starting, stopping and restarting threads.
*
* to the scheduler marking the thread as finished.
*/
-#define CHECK_SENSIBLE_REGS() \
- ASSERT(Hp != 0); \
- ASSERT(Sp != 0); \
- ASSERT(SpLim != 0); \
- ASSERT(HpLim != 0); \
- ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp); \
- ASSERT(HpLim >= Hp);
+#define CHECK_SENSIBLE_REGS() \
+ ASSERT(Hp != 0); \
+ ASSERT(HpAlloc == 0); \
+ ASSERT(Sp != 0); \
+ ASSERT(SpLim != 0); \
+ ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp);
/* -----------------------------------------------------------------------------
Returning from the STG world.
-------------------------------------------------------------------------- */
-INFO_TABLE_RET( stg_stop_thread, STOP_FRAME,
-#if defined(PROFILING)
- W_ unused,
- W_ unused
-#endif
-)
+INFO_TABLE_RET(stg_stop_thread, STOP_FRAME,
+ W_ info_ptr,
+ PROF_HDR_FIELDS(W_,p1,p2))
+/* no return list: explicit stack layout */
{
- /*
+ /*
The final exit.
-
+
The top-top-level closures (e.g., "main") are of type "IO a".
When entered, they perform an IO action and return an 'a' in R1.
-
+
We save R1 on top of the stack where the scheduler can find it,
tidy up the registers and return to the scheduler.
-
+
We Leave the stack looking like this:
-
- +----------------+
+
+ +----------------+
| -------------------> return value
- +----------------+
- | stg_enter_info |
- +----------------+
-
+ +----------------+
+ | stg_enter_info |
+ +----------------+
+
The stg_enter_info is just a dummy info table so that the
garbage collector can understand the stack (there must always
be an info table on top of the stack).
*/
+ // See Note [Unwinding foreign exports on x86-64].
+#if defined(x86_64_HOST_ARCH)
+ unwind UnwindReturnReg = STG_RUN_JMP;
+#else
+ // FIXME: Fill in for other platforms
+ unwind UnwindReturnReg = return;
+#endif
+
Sp = Sp + SIZEOF_StgStopFrame - WDS(2);
Sp(1) = R1;
Sp(0) = stg_enter_info;
StgRegTable_rRet(BaseReg) = ThreadFinished;
R1 = BaseReg;
- jump StgReturn;
+ jump StgReturn [R1];
}
/* -----------------------------------------------------------------------------
the thread's state away nicely.
-------------------------------------------------------------------------- */
-stg_returnToStackTop
+stg_returnToStackTop /* no args: explicit stack layout */
{
LOAD_THREAD_STATE();
CHECK_SENSIBLE_REGS();
- jump %ENTRY_CODE(Sp(0));
+ jump %ENTRY_CODE(Sp(0)) [];
}
-stg_returnToSched
+stg_returnToSched /* no args: explicit stack layout */
{
+ W_ r1;
+ r1 = R1; // foreign calls may clobber R1
SAVE_THREAD_STATE();
foreign "C" threadPaused(MyCapability() "ptr", CurrentTSO);
- jump StgReturn;
+ R1 = r1;
+ jump StgReturn [R1];
}
-// A variant of stg_returntToSched that doesn't call threadPaused() on the
+// A variant of stg_returnToSched that doesn't call threadPaused() on the
// current thread. This is used for switching from compiled execution to the
// interpreter, where calling threadPaused() on every switch would be too
// expensive.
-stg_returnToSchedNotPaused
+//
+// See Note [avoiding threadPaused] in Interpreter.c
+//
+stg_returnToSchedNotPaused /* no args: explicit stack layout */
{
SAVE_THREAD_STATE();
- jump StgReturn;
+ jump StgReturn [R1];
}
// A variant of stg_returnToSched, but instead of returning directly to the
// scheduler, we jump to the code fragment pointed to by R2. This lets us
// perform some final actions after making the thread safe, such as unlocking
// the MVar on which we are about to block in SMP mode.
-stg_returnToSchedButFirst
+stg_returnToSchedButFirst /* no args: explicit stack layout */
{
+ W_ r1, r2, r3;
+ r1 = R1;
+ r2 = R2;
+ r3 = R3;
SAVE_THREAD_STATE();
+ // foreign calls may clobber R1/R2/.., so we save them above
foreign "C" threadPaused(MyCapability() "ptr", CurrentTSO);
- jump R2;
+ R1 = r1;
+ R2 = r2;
+ R3 = r3;
+ jump R2 [R1,R3];
}
-stg_threadFinished
+stg_threadFinished /* no args: explicit stack layout */
{
StgRegTable_rRet(BaseReg) = ThreadFinished;
R1 = BaseReg;
- jump StgReturn;
-}
+ jump StgReturn [R1];
+}
/* -----------------------------------------------------------------------------
Strict IO application - performing an IO action and entering its result.
-
+
rts_evalIO() lets you perform Haskell IO actions from outside of
Haskell-land, returning back to you their result. Want this result
to be evaluated to WHNF by that time, so that we can easily get at
the int/char/whatever using the various get{Ty} functions provided
by the RTS API.
- forceIO takes care of this, performing the IO action and entering the
- results that comes back.
-
- ------------------------------------------------------------------------- */
-
-INFO_TABLE_RET( stg_forceIO, RET_SMALL)
+ stg_forceIO takes care of this, performing the IO action and entering
+ the results that comes back.
-{
- Sp_adj(1);
- ENTER();
-}
-
-/* -----------------------------------------------------------------------------
- Non-strict IO application.
-
- This stack frame works like stg_forceIO_info except that it
- doesn't evaluate the return value. We need the layer because the
- return convention for an IO action differs depending on whether R1
- is a register or not.
------------------------------------------------------------------------- */
-INFO_TABLE_RET( stg_noforceIO, RET_SMALL )
-
+INFO_TABLE_RET(stg_forceIO, RET_SMALL, P_ info_ptr)
+ return (P_ ret)
{
- Sp_adj(1);
- jump %ENTRY_CODE(Sp(0));
+ ENTER(ret);
}
-/* -----------------------------------------------------------------------------
- Special STG entry points for module registration.
- -------------------------------------------------------------------------- */
-
-stg_init_finish
-{
- jump StgReturn;
-}
-
-/* On entry to stg_init:
- * init_stack[0] = &stg_init_ret;
- * init_stack[1] = __stginit_Something;
- */
-stg_init
+/* Called when compiled with -falignment-sanitisation on alignment failure */
+stg_badAlignment_entry
{
- W_ next;
- Sp = W_[BaseReg + OFFSET_StgRegTable_rSp];
- next = W_[Sp];
- Sp_adj(1);
- jump next;
+ foreign "C" barf();
}