1 /* -----------------------------------------------------------------------------
3 * (c) The University of Glasgow 2004
5 * Application-related bits.
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 * -------------------------------------------------------------------------- */
15 /* ----------------------------------------------------------------------------
16 * Evaluate a closure and return it.
18 * There isn't an info table / return address version of stg_ap_0, because
19 * everything being returned is guaranteed evaluated, so it would be a no-op.
22 STRING(stg_ap_0_ret_str,"stg_ap_0_ret... ")
24 stg_ap_0_fast ( P_ fun )
27 ccall debugBelch(stg_ap_0_ret_str);
28 ccall printClosure(R1 "ptr"));
31 ccall checkStackFrame(Sp "ptr"));
36 /* -----------------------------------------------------------------------------
39 This entry code is *only* called by one of the stg_ap functions.
40 On entry: Sp points to the remaining arguments on the stack. If
41 the stack check fails, we can just push the PAP on the stack and
42 return to the scheduler.
44 On entry: R1 points to the PAP. The rest of the function's
45 arguments (apart from those that are already in the PAP) are on the
46 stack, starting at Sp(0). R2 contains an info table which
47 describes these arguments, which is used in the event that the
48 stack check in the entry code below fails. The info table is
49 currently one of the stg_ap_*_ret family, as this code is always
50 entered from those functions.
52 The idea is to copy the chunk of stack from the PAP object onto the
53 stack / into registers, and enter the function.
54 -------------------------------------------------------------------------- */
56 INFO_TABLE(stg_PAP,/*special layout*/0,0,PAP,"PAP","PAP")
57 { ccall barf("PAP object entered!") never returns; }
59 stg_PAP_apply /* no args => explicit stack */
66 Words = TO_W_(StgPAP_n_args(pap));
69 // Check for stack overflow and bump the stack pointer.
70 // We have a hand-rolled stack check fragment here, because none of
71 // the canned ones suit this situation.
73 if (Sp - (WDS(Words) + 2/* see ARG_BCO below */) < SpLim) {
74 // there is a return address in R2 in the event of a
75 // stack check failure. The various stg_apply functions arrange
76 // this before calling stg_PAP_entry.
79 jump stg_gc_unpt_r1 [R1];
87 ccall enterFunCCS(BaseReg "ptr", StgHeader_ccs(pap) "ptr");
93 p = pap + SIZEOF_StgHeader + OFFSET_StgPAP_payload;
103 R1 = StgPAP_fun(pap);
105 /* DEBUGGING CODE, ensures that arity 1 and 2 functions are entered tagged
106 if (TO_W_(StgFunInfoExtra_arity(%FUN_INFO(%INFO_PTR(UNTAG(R1))))) == 1 ) {
112 if (TO_W_(StgFunInfoExtra_arity(%FUN_INFO(%INFO_PTR(UNTAG(R1))))) == 2 ) {
123 jump %GET_ENTRY(UNTAG(R1)) [R1];
126 info = %GET_FUN_INFO(UNTAG(R1));
128 type = TO_W_(StgFunInfoExtra_fun_type(info));
129 if (type == ARG_GEN) {
130 jump StgFunInfoExtra_slow_apply(info) [R1];
132 if (type == ARG_GEN_BIG) {
133 jump StgFunInfoExtra_slow_apply(info) [R1];
135 if (type == ARG_BCO) {
138 Sp(0) = stg_apply_interp_info;
139 jump stg_yield_to_interpreter [];
141 jump W_[stg_ap_stack_entries +
142 WDS(TO_W_(StgFunInfoExtra_fun_type(info)))] [R1];
146 /* -----------------------------------------------------------------------------
147 Entry Code for an AP (a PAP with arity zero).
149 The entry code is very similar to a PAP, except there are no
150 further arguments on the stack to worry about, so the stack check
151 is simpler. We must also push an update frame on the stack before
152 applying the function.
153 -------------------------------------------------------------------------- */
155 INFO_TABLE(stg_AP,/*special layout*/0,0,AP,"AP","AP")
156 /* no args => explicit stack */
163 Words = TO_W_(StgAP_n_args(ap));
166 * Check for stack overflow. IMPORTANT: use a _ENTER check here,
167 * because if the check fails, we might end up blackholing this very
168 * closure, in which case we must enter the blackhole on return rather
169 * than continuing to evaluate the now-defunct closure.
171 STK_CHK_ENTER(WDS(Words) +
172 SIZEOF_StgUpdateFrame +
173 2/* see ARG_BCO below */, R1);
175 PUSH_UPD_FRAME(Sp - SIZEOF_StgUpdateFrame, R1);
176 Sp = Sp - SIZEOF_StgUpdateFrame - WDS(Words);
185 p = ap + SIZEOF_StgHeader + OFFSET_StgAP_payload;
201 jump %GET_ENTRY(UNTAG(R1)) [R1];
204 info = %GET_FUN_INFO(UNTAG(R1));
206 type = TO_W_(StgFunInfoExtra_fun_type(info));
207 if (type == ARG_GEN) {
208 jump StgFunInfoExtra_slow_apply(info) [R1];
210 if (type == ARG_GEN_BIG) {
211 jump StgFunInfoExtra_slow_apply(info) [R1];
213 if (type == ARG_BCO) {
216 Sp(0) = stg_apply_interp_info;
217 jump stg_yield_to_interpreter [];
219 jump W_[stg_ap_stack_entries +
220 WDS(TO_W_(StgFunInfoExtra_fun_type(info)))] [R1];
224 /* AP_NOUPD is exactly like AP, except that no update frame is pushed.
225 Use for thunks that are guaranteed to be entered once only, such as
226 those generated by the byte-code compiler for inserting breakpoints. */
228 INFO_TABLE(stg_AP_NOUPD,/*special layout*/0,0,AP,"AP_NOUPD","AP_NOUPD")
229 /* no args => explicit stack */
236 Words = TO_W_(StgAP_n_args(ap));
239 * Check for stack overflow. IMPORTANT: use a _ENTER check here,
240 * because if the check fails, we might end up blackholing this very
241 * closure, in which case we must enter the blackhole on return rather
242 * than continuing to evaluate the now-defunct closure.
244 STK_CHK_ENTER(WDS(Words) +
245 2/* see ARG_BCO below */, R1);
246 Sp = Sp - WDS(Words);
255 p = ap + SIZEOF_StgHeader + OFFSET_StgAP_payload;
271 jump %GET_ENTRY(UNTAG(R1)) [R1];
274 info = %GET_FUN_INFO(UNTAG(R1));
276 type = TO_W_(StgFunInfoExtra_fun_type(info));
277 if (type == ARG_GEN) {
278 jump StgFunInfoExtra_slow_apply(info) [R1];
280 if (type == ARG_GEN_BIG) {
281 jump StgFunInfoExtra_slow_apply(info) [R1];
283 if (type == ARG_BCO) {
286 Sp(0) = stg_apply_interp_info;
287 jump stg_yield_to_interpreter [];
289 jump W_[stg_ap_stack_entries +
290 WDS(TO_W_(StgFunInfoExtra_fun_type(info)))] [R1];
294 /* -----------------------------------------------------------------------------
295 Entry Code for an AP_STACK.
297 Very similar to a PAP and AP. The layout is the same as PAP
298 and AP, except that the payload is a chunk of stack instead of
299 being described by the function's info table. Like an AP,
300 there are no further arguments on the stack to worry about.
301 However, the function closure (ap->fun) does not necessarily point
302 directly to a function, so we have to enter it using stg_ap_0.
303 -------------------------------------------------------------------------- */
305 INFO_TABLE(stg_AP_STACK,/*special layout*/0,0,AP_STACK,"AP_STACK","AP_STACK")
306 /* no args => explicit stack */
313 Words = StgAP_STACK_size(ap);
316 * Check for stack overflow. IMPORTANT: use a _ENTER check here,
317 * because if the check fails, we might end up blackholing this very
318 * closure, in which case we must enter the blackhole on return rather
319 * than continuing to evaluate the now-defunct closure.
321 STK_CHK_ENTER(WDS(Words) + SIZEOF_StgUpdateFrame + WDS(AP_STACK_SPLIM), R1);
322 /* ensure there is at least AP_STACK_SPLIM words of headroom available
323 * after unpacking the AP_STACK. See bug #1466 */
325 PUSH_UPD_FRAME(Sp - SIZEOF_StgUpdateFrame, R1);
326 Sp = Sp - SIZEOF_StgUpdateFrame - WDS(Words);
335 p = ap + SIZEOF_StgHeader + OFFSET_StgAP_STACK_payload;
348 R1 = StgAP_STACK_fun(ap);
353 /* -----------------------------------------------------------------------------
354 AP_STACK_NOUPD - exactly like AP_STACK, but doesn't push an update frame.
355 -------------------------------------------------------------------------- */
357 INFO_TABLE(stg_AP_STACK_NOUPD,/*special layout*/0,0,AP_STACK,
358 "AP_STACK_NOUPD","AP_STACK_NOUPD")
359 /* no args => explicit stack */
366 Words = StgAP_STACK_size(ap);
369 * Check for stack overflow. IMPORTANT: use a _NP check here,
370 * because if the check fails, we might end up blackholing this very
371 * closure, in which case we must enter the blackhole on return rather
372 * than continuing to evaluate the now-defunct closure.
374 STK_CHK_ENTER(WDS(Words) + WDS(AP_STACK_SPLIM), R1);
375 /* ensure there is at least AP_STACK_SPLIM words of headroom available
376 * after unpacking the AP_STACK. See bug #1466 */
378 Sp = Sp - WDS(Words);
387 p = ap + SIZEOF_StgHeader + OFFSET_StgAP_STACK_payload;
400 R1 = StgAP_STACK_fun(ap);