1 /* -----------------------------------------------------------------------------
4 * Copyright (c) The GHC Team, 1994-2002.
5 * ---------------------------------------------------------------------------*/
7 #include "PosixSource.h"
15 #include "LdvProfile.h"
21 #include "Bytecodes.h"
23 #include "Disassembler.h"
24 #include "Interpreter.h"
26 #include <string.h> /* for memcpy */
32 /* --------------------------------------------------------------------------
33 * The bytecode interpreter
34 * ------------------------------------------------------------------------*/
36 /* Gather stats about entry, opcode, opcode-pair frequencies. For
37 tuning the interpreter. */
39 /* #define INTERP_STATS */
42 /* Sp points to the lowest live word on the stack. */
44 #define BCO_NEXT instrs[bciPtr++]
45 #define BCO_NEXT_32 (bciPtr += 2, (((StgWord) instrs[bciPtr-2]) << 16) + ((StgWord) instrs[bciPtr-1]))
46 #define BCO_NEXT_64 (bciPtr += 4, (((StgWord) instrs[bciPtr-4]) << 48) + (((StgWord) instrs[bciPtr-3]) << 32) + (((StgWord) instrs[bciPtr-2]) << 16) + ((StgWord) instrs[bciPtr-1]))
47 #if WORD_SIZE_IN_BITS == 32
48 #define BCO_NEXT_WORD BCO_NEXT_32
49 #elif WORD_SIZE_IN_BITS == 64
50 #define BCO_NEXT_WORD BCO_NEXT_64
52 #error Cannot cope with WORD_SIZE_IN_BITS being nether 32 nor 64
54 #define BCO_GET_LARGE_ARG ((bci & bci_FLAG_LARGE_ARGS) ? BCO_NEXT_WORD : BCO_NEXT)
56 #define BCO_PTR(n) (W_)ptrs[n]
57 #define BCO_LIT(n) literals[n]
59 #define LOAD_STACK_POINTERS \
60 Sp = cap->r.rCurrentTSO->sp; \
61 /* We don't change this ... */ \
62 SpLim = cap->r.rCurrentTSO->stack + RESERVED_STACK_WORDS;
64 #define SAVE_STACK_POINTERS \
65 cap->r.rCurrentTSO->sp = Sp
67 #define RETURN_TO_SCHEDULER(todo,retcode) \
68 SAVE_STACK_POINTERS; \
69 cap->r.rCurrentTSO->what_next = (todo); \
70 threadPaused(cap,cap->r.rCurrentTSO); \
71 cap->r.rRet = (retcode); \
74 #define RETURN_TO_SCHEDULER_NO_PAUSE(todo,retcode) \
75 SAVE_STACK_POINTERS; \
76 cap->r.rCurrentTSO->what_next = (todo); \
77 cap->r.rRet = (retcode); \
82 allocate_NONUPD (int n_words
)
84 return allocate(stg_max(sizeofW(StgHeader
)+MIN_PAYLOAD_SIZE
, n_words
));
87 int rts_stop_next_breakpoint
= 0;
88 int rts_stop_on_exception
= 0;
92 /* Hacky stats, for tuning the interpreter ... */
93 int it_unknown_entries
[N_CLOSURE_TYPES
];
94 int it_total_unknown_entries
;
106 int it_oofreq
[27][27];
110 #define INTERP_TICK(n) (n)++
112 void interp_startup ( void )
115 it_retto_BCO
= it_retto_UPDATE
= it_retto_other
= 0;
116 it_total_entries
= it_total_unknown_entries
= 0;
117 for (i
= 0; i
< N_CLOSURE_TYPES
; i
++)
118 it_unknown_entries
[i
] = 0;
119 it_slides
= it_insns
= it_BCO_entries
= 0;
120 for (i
= 0; i
< 27; i
++) it_ofreq
[i
] = 0;
121 for (i
= 0; i
< 27; i
++)
122 for (j
= 0; j
< 27; j
++)
127 void interp_shutdown ( void )
129 int i
, j
, k
, o_max
, i_max
, j_max
;
130 debugBelch("%d constrs entered -> (%d BCO, %d UPD, %d ??? )\n",
131 it_retto_BCO
+ it_retto_UPDATE
+ it_retto_other
,
132 it_retto_BCO
, it_retto_UPDATE
, it_retto_other
);
133 debugBelch("%d total entries, %d unknown entries \n",
134 it_total_entries
, it_total_unknown_entries
);
135 for (i
= 0; i
< N_CLOSURE_TYPES
; i
++) {
136 if (it_unknown_entries
[i
] == 0) continue;
137 debugBelch(" type %2d: unknown entries (%4.1f%%) == %d\n",
138 i
, 100.0 * ((double)it_unknown_entries
[i
]) /
139 ((double)it_total_unknown_entries
),
140 it_unknown_entries
[i
]);
142 debugBelch("%d insns, %d slides, %d BCO_entries\n",
143 it_insns
, it_slides
, it_BCO_entries
);
144 for (i
= 0; i
< 27; i
++)
145 debugBelch("opcode %2d got %d\n", i
, it_ofreq
[i
] );
147 for (k
= 1; k
< 20; k
++) {
150 for (i
= 0; i
< 27; i
++) {
151 for (j
= 0; j
< 27; j
++) {
152 if (it_oofreq
[i
][j
] > o_max
) {
153 o_max
= it_oofreq
[i
][j
];
154 i_max
= i
; j_max
= j
;
159 debugBelch("%d: count (%4.1f%%) %6d is %d then %d\n",
160 k
, ((double)o_max
) * 100.0 / ((double)it_insns
), o_max
,
162 it_oofreq
[i_max
][j_max
] = 0;
167 #else // !INTERP_STATS
169 #define INTERP_TICK(n) /* nothing */
173 static StgWord app_ptrs_itbl
[] = {
176 (W_
)&stg_ap_ppp_info
,
177 (W_
)&stg_ap_pppp_info
,
178 (W_
)&stg_ap_ppppp_info
,
179 (W_
)&stg_ap_pppppp_info
,
182 HsStablePtr rts_breakpoint_io_action
; // points to the IO action which is executed on a breakpoint
183 // it is set in main/GHC.hs:runStmt
186 interpretBCO (Capability
* cap
)
188 // Use of register here is primarily to make it clear to compilers
189 // that these entities are non-aliasable.
190 register StgPtr Sp
; // local state -- stack pointer
191 register StgPtr SpLim
; // local state -- stack lim pointer
192 register StgClosure
* obj
;
197 // ------------------------------------------------------------------------
200 // We have a closure to evaluate. Stack looks like:
204 // Sp | -------------------> closure
207 if (Sp
[0] == (W_
)&stg_enter_info
) {
212 // ------------------------------------------------------------------------
215 // We have a BCO application to perform. Stack looks like:
226 else if (Sp
[0] == (W_
)&stg_apply_interp_info
) {
227 obj
= UNTAG_CLOSURE((StgClosure
*)Sp
[1]);
232 // ------------------------------------------------------------------------
235 // We have an unboxed value to return. See comment before
236 // do_return_unboxed, below.
239 goto do_return_unboxed
;
242 // Evaluate the object on top of the stack.
244 obj
= (StgClosure
*)Sp
[0]; Sp
++;
247 obj
= UNTAG_CLOSURE(obj
);
248 INTERP_TICK(it_total_evals
);
250 IF_DEBUG(interpreter
,
252 "\n---------------------------------------------------------------\n");
253 debugBelch("Evaluating: "); printObj(obj
);
254 debugBelch("Sp = %p\n", Sp
);
257 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
261 IF_DEBUG(sanity
,checkStackChunk(Sp
, cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
));
263 switch ( get_itbl(obj
)->type
) {
268 case IND_OLDGEN_PERM
:
271 obj
= ((StgInd
*)obj
)->indirectee
;
282 case CONSTR_NOCAF_STATIC
:
296 ASSERT(((StgBCO
*)obj
)->arity
> 0);
300 case AP
: /* Copied from stg_AP_entry. */
309 if (Sp
- (words
+sizeofW(StgUpdateFrame
)) < SpLim
) {
312 Sp
[0] = (W_
)&stg_enter_info
;
313 RETURN_TO_SCHEDULER(ThreadInterpret
, StackOverflow
);
316 /* Ok; we're safe. Party on. Push an update frame. */
317 Sp
-= sizeofW(StgUpdateFrame
);
319 StgUpdateFrame
*__frame
;
320 __frame
= (StgUpdateFrame
*)Sp
;
321 SET_INFO(__frame
, (StgInfoTable
*)&stg_upd_frame_info
);
322 __frame
->updatee
= (StgClosure
*)(ap
);
325 /* Reload the stack */
327 for (i
=0; i
< words
; i
++) {
328 Sp
[i
] = (W_
)ap
->payload
[i
];
331 obj
= UNTAG_CLOSURE((StgClosure
*)ap
->fun
);
332 ASSERT(get_itbl(obj
)->type
== BCO
);
341 j
= get_itbl(obj
)->type
;
342 ASSERT(j
>= 0 && j
< N_CLOSURE_TYPES
);
343 it_unknown_entries
[j
]++;
344 it_total_unknown_entries
++;
348 // Can't handle this object; yield to scheduler
349 IF_DEBUG(interpreter
,
350 debugBelch("evaluating unknown closure -- yielding to sched\n");
355 Sp
[0] = (W_
)&stg_enter_info
;
356 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
360 // ------------------------------------------------------------------------
361 // We now have an evaluated object (obj). The next thing to
362 // do is return it to the stack frame on top of the stack.
364 ASSERT(closure_HNF(obj
));
366 IF_DEBUG(interpreter
,
368 "\n---------------------------------------------------------------\n");
369 debugBelch("Returning: "); printObj(obj
);
370 debugBelch("Sp = %p\n", Sp
);
372 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
376 IF_DEBUG(sanity
,checkStackChunk(Sp
, cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
));
378 switch (get_itbl((StgClosure
*)Sp
)->type
) {
381 const StgInfoTable
*info
;
383 // NOTE: not using get_itbl().
384 info
= ((StgClosure
*)Sp
)->header
.info
;
385 if (info
== (StgInfoTable
*)&stg_ap_v_info
) {
386 n
= 1; m
= 0; goto do_apply
;
388 if (info
== (StgInfoTable
*)&stg_ap_f_info
) {
389 n
= 1; m
= 1; goto do_apply
;
391 if (info
== (StgInfoTable
*)&stg_ap_d_info
) {
392 n
= 1; m
= sizeofW(StgDouble
); goto do_apply
;
394 if (info
== (StgInfoTable
*)&stg_ap_l_info
) {
395 n
= 1; m
= sizeofW(StgInt64
); goto do_apply
;
397 if (info
== (StgInfoTable
*)&stg_ap_n_info
) {
398 n
= 1; m
= 1; goto do_apply
;
400 if (info
== (StgInfoTable
*)&stg_ap_p_info
) {
401 n
= 1; m
= 1; goto do_apply
;
403 if (info
== (StgInfoTable
*)&stg_ap_pp_info
) {
404 n
= 2; m
= 2; goto do_apply
;
406 if (info
== (StgInfoTable
*)&stg_ap_ppp_info
) {
407 n
= 3; m
= 3; goto do_apply
;
409 if (info
== (StgInfoTable
*)&stg_ap_pppp_info
) {
410 n
= 4; m
= 4; goto do_apply
;
412 if (info
== (StgInfoTable
*)&stg_ap_ppppp_info
) {
413 n
= 5; m
= 5; goto do_apply
;
415 if (info
== (StgInfoTable
*)&stg_ap_pppppp_info
) {
416 n
= 6; m
= 6; goto do_apply
;
418 goto do_return_unrecognised
;
422 // Returning to an update frame: do the update, pop the update
423 // frame, and continue with the next stack frame.
424 INTERP_TICK(it_retto_UPDATE
);
425 UPD_IND(((StgUpdateFrame
*)Sp
)->updatee
, obj
);
426 Sp
+= sizeofW(StgUpdateFrame
);
430 // Returning to an interpreted continuation: put the object on
431 // the stack, and start executing the BCO.
432 INTERP_TICK(it_retto_BCO
);
435 obj
= (StgClosure
*)Sp
[2];
436 ASSERT(get_itbl(obj
)->type
== BCO
);
440 do_return_unrecognised
:
442 // Can't handle this return address; yield to scheduler
443 INTERP_TICK(it_retto_other
);
444 IF_DEBUG(interpreter
,
445 debugBelch("returning to unknown frame -- yielding to sched\n");
446 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
450 Sp
[0] = (W_
)&stg_enter_info
;
451 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
455 // -------------------------------------------------------------------------
456 // Returning an unboxed value. The stack looks like this:
473 // where XXXX_info is one of the stg_gc_unbx_r1_info family.
475 // We're only interested in the case when the real return address
476 // is a BCO; otherwise we'll return to the scheduler.
482 ASSERT( Sp
[0] == (W_
)&stg_gc_unbx_r1_info
483 || Sp
[0] == (W_
)&stg_gc_unpt_r1_info
484 || Sp
[0] == (W_
)&stg_gc_f1_info
485 || Sp
[0] == (W_
)&stg_gc_d1_info
486 || Sp
[0] == (W_
)&stg_gc_l1_info
487 || Sp
[0] == (W_
)&stg_gc_void_info
// VoidRep
490 // get the offset of the stg_ctoi_ret_XXX itbl
491 offset
= stack_frame_sizeW((StgClosure
*)Sp
);
493 switch (get_itbl((StgClosure
*)Sp
+offset
)->type
) {
496 // Returning to an interpreted continuation: put the object on
497 // the stack, and start executing the BCO.
498 INTERP_TICK(it_retto_BCO
);
499 obj
= (StgClosure
*)Sp
[offset
+1];
500 ASSERT(get_itbl(obj
)->type
== BCO
);
501 goto run_BCO_return_unboxed
;
505 // Can't handle this return address; yield to scheduler
506 INTERP_TICK(it_retto_other
);
507 IF_DEBUG(interpreter
,
508 debugBelch("returning to unknown frame -- yielding to sched\n");
509 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
511 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
518 // -------------------------------------------------------------------------
522 // we have a function to apply (obj), and n arguments taking up m
523 // words on the stack. The info table (stg_ap_pp_info or whatever)
524 // is on top of the arguments on the stack.
526 switch (get_itbl(obj
)->type
) {
534 // we only cope with PAPs whose function is a BCO
535 if (get_itbl(UNTAG_CLOSURE(pap
->fun
))->type
!= BCO
) {
536 goto defer_apply_to_sched
;
543 // n must be greater than 1, and the only kinds of
544 // application we support with more than one argument
545 // are all pointers...
547 // Shuffle the args for this function down, and put
548 // the appropriate info table in the gap.
549 for (i
= 0; i
< arity
; i
++) {
550 Sp
[(int)i
-1] = Sp
[i
];
551 // ^^^^^ careful, i-1 might be negative, but i in unsigned
553 Sp
[arity
-1] = app_ptrs_itbl
[n
-arity
-1];
555 // unpack the PAP's arguments onto the stack
557 for (i
= 0; i
< pap
->n_args
; i
++) {
558 Sp
[i
] = (W_
)pap
->payload
[i
];
560 obj
= UNTAG_CLOSURE(pap
->fun
);
563 else if (arity
== n
) {
565 for (i
= 0; i
< pap
->n_args
; i
++) {
566 Sp
[i
] = (W_
)pap
->payload
[i
];
568 obj
= UNTAG_CLOSURE(pap
->fun
);
571 else /* arity > n */ {
572 // build a new PAP and return it.
574 new_pap
= (StgPAP
*)allocate(PAP_sizeW(pap
->n_args
+ m
));
575 SET_HDR(new_pap
,&stg_PAP_info
,CCCS
);
576 new_pap
->arity
= pap
->arity
- n
;
577 new_pap
->n_args
= pap
->n_args
+ m
;
578 new_pap
->fun
= pap
->fun
;
579 for (i
= 0; i
< pap
->n_args
; i
++) {
580 new_pap
->payload
[i
] = pap
->payload
[i
];
582 for (i
= 0; i
< m
; i
++) {
583 new_pap
->payload
[pap
->n_args
+ i
] = (StgClosure
*)Sp
[i
];
585 obj
= (StgClosure
*)new_pap
;
595 arity
= ((StgBCO
*)obj
)->arity
;
598 // n must be greater than 1, and the only kinds of
599 // application we support with more than one argument
600 // are all pointers...
602 // Shuffle the args for this function down, and put
603 // the appropriate info table in the gap.
604 for (i
= 0; i
< arity
; i
++) {
605 Sp
[(int)i
-1] = Sp
[i
];
606 // ^^^^^ careful, i-1 might be negative, but i in unsigned
608 Sp
[arity
-1] = app_ptrs_itbl
[n
-arity
-1];
612 else if (arity
== n
) {
615 else /* arity > n */ {
616 // build a PAP and return it.
619 pap
= (StgPAP
*)allocate(PAP_sizeW(m
));
620 SET_HDR(pap
, &stg_PAP_info
,CCCS
);
621 pap
->arity
= arity
- n
;
624 for (i
= 0; i
< m
; i
++) {
625 pap
->payload
[i
] = (StgClosure
*)Sp
[i
];
627 obj
= (StgClosure
*)pap
;
633 // No point in us applying machine-code functions
635 defer_apply_to_sched
:
638 Sp
[0] = (W_
)&stg_enter_info
;
639 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
642 // ------------------------------------------------------------------------
643 // Ok, we now have a bco (obj), and its arguments are all on the
644 // stack. We can start executing the byte codes.
646 // The stack is in one of two states. First, if this BCO is a
656 // Second, if this BCO is a continuation:
671 // where retval is the value being returned to this continuation.
672 // In the event of a stack check, heap check, or context switch,
673 // we need to leave the stack in a sane state so the garbage
674 // collector can find all the pointers.
676 // (1) BCO is a function: the BCO's bitmap describes the
677 // pointerhood of the arguments.
679 // (2) BCO is a continuation: BCO's bitmap describes the
680 // pointerhood of the free variables.
682 // Sadly we have three different kinds of stack/heap/cswitch check
688 if (doYouWantToGC()) {
689 Sp
--; Sp
[0] = (W_
)&stg_enter_info
;
690 RETURN_TO_SCHEDULER(ThreadInterpret
, HeapOverflow
);
692 // Stack checks aren't necessary at return points, the stack use
693 // is aggregated into the enclosing function entry point.
697 run_BCO_return_unboxed
:
699 if (doYouWantToGC()) {
700 RETURN_TO_SCHEDULER(ThreadInterpret
, HeapOverflow
);
702 // Stack checks aren't necessary at return points, the stack use
703 // is aggregated into the enclosing function entry point.
711 Sp
[0] = (W_
)&stg_apply_interp_info
;
712 checkStackChunk(Sp
,SpLim
);
717 if (doYouWantToGC()) {
720 Sp
[0] = (W_
)&stg_apply_interp_info
; // placeholder, really
721 RETURN_TO_SCHEDULER(ThreadInterpret
, HeapOverflow
);
725 if (Sp
- INTERP_STACK_CHECK_THRESH
< SpLim
) {
728 Sp
[0] = (W_
)&stg_apply_interp_info
; // placeholder, really
729 RETURN_TO_SCHEDULER(ThreadInterpret
, StackOverflow
);
734 // Now, actually interpret the BCO... (no returning to the
735 // scheduler again until the stack is in an orderly state).
737 INTERP_TICK(it_BCO_entries
);
739 register int bciPtr
= 1; /* instruction pointer */
740 register StgWord16 bci
;
741 register StgBCO
* bco
= (StgBCO
*)obj
;
742 register StgWord16
* instrs
= (StgWord16
*)(bco
->instrs
->payload
);
743 register StgWord
* literals
= (StgWord
*)(&bco
->literals
->payload
[0]);
744 register StgPtr
* ptrs
= (StgPtr
*)(&bco
->ptrs
->payload
[0]);
747 it_lastopc
= 0; /* no opcode */
751 ASSERT(bciPtr
<= instrs
[0]);
752 IF_DEBUG(interpreter
,
753 //if (do_print_stack) {
754 //debugBelch("\n-- BEGIN stack\n");
755 //printStack(Sp,cap->r.rCurrentTSO->stack+cap->r.rCurrentTSO->stack_size,iSu);
756 //debugBelch("-- END stack\n\n");
758 debugBelch("Sp = %p pc = %d ", Sp
, bciPtr
);
759 disInstr(bco
,bciPtr
);
762 for (i
= 8; i
>= 0; i
--) {
763 debugBelch("%d %p\n", i
, (StgPtr
)(*(Sp
+i
)));
767 //if (do_print_stack) checkStack(Sp,cap->r.rCurrentTSO->stack+cap->r.rCurrentTSO->stack_size,iSu);
771 INTERP_TICK(it_insns
);
774 ASSERT( (int)instrs
[bciPtr
] >= 0 && (int)instrs
[bciPtr
] < 27 );
775 it_ofreq
[ (int)instrs
[bciPtr
] ] ++;
776 it_oofreq
[ it_lastopc
][ (int)instrs
[bciPtr
] ] ++;
777 it_lastopc
= (int)instrs
[bciPtr
];
781 /* We use the high 8 bits for flags, only the highest of which is
782 * currently allocated */
783 ASSERT((bci
& 0xFF00) == (bci
& 0x8000));
785 switch (bci
& 0xFF) {
787 /* check for a breakpoint on the beginning of a let binding */
790 int arg1_brk_array
, arg2_array_index
, arg3_freeVars
;
791 StgArrWords
*breakPoints
;
792 int returning_from_break
; // are we resuming execution from a breakpoint?
793 // if yes, then don't break this time around
794 StgClosure
*ioAction
; // the io action to run at a breakpoint
796 StgAP_STACK
*new_aps
; // a closure to save the top stack frame on the heap
800 arg1_brk_array
= BCO_NEXT
; // 1st arg of break instruction
801 arg2_array_index
= BCO_NEXT
; // 2nd arg of break instruction
802 arg3_freeVars
= BCO_NEXT
; // 3rd arg of break instruction
804 // check if we are returning from a breakpoint - this info
805 // is stored in the flags field of the current TSO
806 returning_from_break
= cap
->r
.rCurrentTSO
->flags
& TSO_STOPPED_ON_BREAKPOINT
;
808 // if we are returning from a break then skip this section
809 // and continue executing
810 if (!returning_from_break
)
812 breakPoints
= (StgArrWords
*) BCO_PTR(arg1_brk_array
);
814 // stop the current thread if either the
815 // "rts_stop_next_breakpoint" flag is true OR if the
816 // breakpoint flag for this particular expression is
818 if (rts_stop_next_breakpoint
== rtsTrue
||
819 breakPoints
->payload
[arg2_array_index
] == rtsTrue
)
821 // make sure we don't automatically stop at the
823 rts_stop_next_breakpoint
= rtsFalse
;
825 // allocate memory for a new AP_STACK, enough to
826 // store the top stack frame plus an
827 // stg_apply_interp_info pointer and a pointer to
829 size_words
= BCO_BITMAP_SIZE(obj
) + 2;
830 new_aps
= (StgAP_STACK
*) allocate (AP_STACK_sizeW(size_words
));
831 SET_HDR(new_aps
,&stg_AP_STACK_info
,CCS_SYSTEM
);
832 new_aps
->size
= size_words
;
833 new_aps
->fun
= &stg_dummy_ret_closure
;
835 // fill in the payload of the AP_STACK
836 new_aps
->payload
[0] = (StgClosure
*)&stg_apply_interp_info
;
837 new_aps
->payload
[1] = (StgClosure
*)obj
;
839 // copy the contents of the top stack frame into the AP_STACK
840 for (i
= 2; i
< size_words
; i
++)
842 new_aps
->payload
[i
] = (StgClosure
*)Sp
[i
-2];
845 // prepare the stack so that we can call the
846 // rts_breakpoint_io_action and ensure that the stack is
847 // in a reasonable state for the GC and so that
848 // execution of this BCO can continue when we resume
849 ioAction
= (StgClosure
*) deRefStablePtr (rts_breakpoint_io_action
);
852 Sp
[7] = (W_
)&stg_apply_interp_info
;
853 Sp
[6] = (W_
)&stg_noforceIO_info
; // see [unreg] below
854 Sp
[5] = (W_
)new_aps
; // the AP_STACK
855 Sp
[4] = (W_
)BCO_PTR(arg3_freeVars
); // the info about local vars of the breakpoint
856 Sp
[3] = (W_
)False_closure
; // True <=> a breakpoint
857 Sp
[2] = (W_
)&stg_ap_pppv_info
;
858 Sp
[1] = (W_
)ioAction
; // apply the IO action to its two arguments above
859 Sp
[0] = (W_
)&stg_enter_info
; // get ready to run the IO action
860 // Note [unreg]: in unregisterised mode, the return
861 // convention for IO is different. The
862 // stg_noForceIO_info stack frame is necessary to
863 // account for this difference.
865 // set the flag in the TSO to say that we are now
866 // stopping at a breakpoint so that when we resume
867 // we don't stop on the same breakpoint that we
868 // already stopped at just now
869 cap
->r
.rCurrentTSO
->flags
|= TSO_STOPPED_ON_BREAKPOINT
;
871 // stop this thread and return to the scheduler -
872 // eventually we will come back and the IO action on
873 // the top of the stack will be executed
874 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
877 // record that this thread is not stopped at a breakpoint anymore
878 cap
->r
.rCurrentTSO
->flags
&= ~TSO_STOPPED_ON_BREAKPOINT
;
880 // continue normal execution of the byte code instructions
885 // Explicit stack check at the beginning of a function
886 // *only* (stack checks in case alternatives are
887 // propagated to the enclosing function).
888 StgWord stk_words_reqd
= BCO_GET_LARGE_ARG
+ 1;
889 if (Sp
- stk_words_reqd
< SpLim
) {
892 Sp
[0] = (W_
)&stg_apply_interp_info
;
893 RETURN_TO_SCHEDULER(ThreadInterpret
, StackOverflow
);
928 Sp
[-1] = BCO_PTR(o1
);
933 case bci_PUSH_ALTS
: {
934 int o_bco
= BCO_NEXT
;
935 Sp
[-2] = (W_
)&stg_ctoi_R1p_info
;
936 Sp
[-1] = BCO_PTR(o_bco
);
941 case bci_PUSH_ALTS_P
: {
942 int o_bco
= BCO_NEXT
;
943 Sp
[-2] = (W_
)&stg_ctoi_R1unpt_info
;
944 Sp
[-1] = BCO_PTR(o_bco
);
949 case bci_PUSH_ALTS_N
: {
950 int o_bco
= BCO_NEXT
;
951 Sp
[-2] = (W_
)&stg_ctoi_R1n_info
;
952 Sp
[-1] = BCO_PTR(o_bco
);
957 case bci_PUSH_ALTS_F
: {
958 int o_bco
= BCO_NEXT
;
959 Sp
[-2] = (W_
)&stg_ctoi_F1_info
;
960 Sp
[-1] = BCO_PTR(o_bco
);
965 case bci_PUSH_ALTS_D
: {
966 int o_bco
= BCO_NEXT
;
967 Sp
[-2] = (W_
)&stg_ctoi_D1_info
;
968 Sp
[-1] = BCO_PTR(o_bco
);
973 case bci_PUSH_ALTS_L
: {
974 int o_bco
= BCO_NEXT
;
975 Sp
[-2] = (W_
)&stg_ctoi_L1_info
;
976 Sp
[-1] = BCO_PTR(o_bco
);
981 case bci_PUSH_ALTS_V
: {
982 int o_bco
= BCO_NEXT
;
983 Sp
[-2] = (W_
)&stg_ctoi_V_info
;
984 Sp
[-1] = BCO_PTR(o_bco
);
989 case bci_PUSH_APPLY_N
:
990 Sp
--; Sp
[0] = (W_
)&stg_ap_n_info
;
992 case bci_PUSH_APPLY_V
:
993 Sp
--; Sp
[0] = (W_
)&stg_ap_v_info
;
995 case bci_PUSH_APPLY_F
:
996 Sp
--; Sp
[0] = (W_
)&stg_ap_f_info
;
998 case bci_PUSH_APPLY_D
:
999 Sp
--; Sp
[0] = (W_
)&stg_ap_d_info
;
1001 case bci_PUSH_APPLY_L
:
1002 Sp
--; Sp
[0] = (W_
)&stg_ap_l_info
;
1004 case bci_PUSH_APPLY_P
:
1005 Sp
--; Sp
[0] = (W_
)&stg_ap_p_info
;
1007 case bci_PUSH_APPLY_PP
:
1008 Sp
--; Sp
[0] = (W_
)&stg_ap_pp_info
;
1010 case bci_PUSH_APPLY_PPP
:
1011 Sp
--; Sp
[0] = (W_
)&stg_ap_ppp_info
;
1013 case bci_PUSH_APPLY_PPPP
:
1014 Sp
--; Sp
[0] = (W_
)&stg_ap_pppp_info
;
1016 case bci_PUSH_APPLY_PPPPP
:
1017 Sp
--; Sp
[0] = (W_
)&stg_ap_ppppp_info
;
1019 case bci_PUSH_APPLY_PPPPPP
:
1020 Sp
--; Sp
[0] = (W_
)&stg_ap_pppppp_info
;
1023 case bci_PUSH_UBX
: {
1025 int o_lits
= BCO_NEXT
;
1026 int n_words
= BCO_NEXT
;
1028 for (i
= 0; i
< n_words
; i
++) {
1029 Sp
[i
] = (W_
)BCO_LIT(o_lits
+i
);
1037 /* a_1, .. a_n, b_1, .. b_by, s => a_1, .. a_n, s */
1042 INTERP_TICK(it_slides
);
1046 case bci_ALLOC_AP
: {
1048 int n_payload
= BCO_NEXT
;
1049 ap
= (StgAP
*)allocate(AP_sizeW(n_payload
));
1051 ap
->n_args
= n_payload
;
1052 SET_HDR(ap
, &stg_AP_info
, CCS_SYSTEM
/*ToDo*/)
1057 case bci_ALLOC_AP_NOUPD
: {
1059 int n_payload
= BCO_NEXT
;
1060 ap
= (StgAP
*)allocate(AP_sizeW(n_payload
));
1062 ap
->n_args
= n_payload
;
1063 SET_HDR(ap
, &stg_AP_NOUPD_info
, CCS_SYSTEM
/*ToDo*/)
1068 case bci_ALLOC_PAP
: {
1070 int arity
= BCO_NEXT
;
1071 int n_payload
= BCO_NEXT
;
1072 pap
= (StgPAP
*)allocate(PAP_sizeW(n_payload
));
1074 pap
->n_args
= n_payload
;
1076 SET_HDR(pap
, &stg_PAP_info
, CCS_SYSTEM
/*ToDo*/)
1083 int stkoff
= BCO_NEXT
;
1084 int n_payload
= BCO_NEXT
;
1085 StgAP
* ap
= (StgAP
*)Sp
[stkoff
];
1086 ASSERT((int)ap
->n_args
== n_payload
);
1087 ap
->fun
= (StgClosure
*)Sp
[0];
1089 // The function should be a BCO, and its bitmap should
1090 // cover the payload of the AP correctly.
1091 ASSERT(get_itbl(ap
->fun
)->type
== BCO
1092 && BCO_BITMAP_SIZE(ap
->fun
) == ap
->n_args
);
1094 for (i
= 0; i
< n_payload
; i
++)
1095 ap
->payload
[i
] = (StgClosure
*)Sp
[i
+1];
1097 IF_DEBUG(interpreter
,
1098 debugBelch("\tBuilt ");
1099 printObj((StgClosure
*)ap
);
1106 int stkoff
= BCO_NEXT
;
1107 int n_payload
= BCO_NEXT
;
1108 StgPAP
* pap
= (StgPAP
*)Sp
[stkoff
];
1109 ASSERT((int)pap
->n_args
== n_payload
);
1110 pap
->fun
= (StgClosure
*)Sp
[0];
1112 // The function should be a BCO
1113 ASSERT(get_itbl(pap
->fun
)->type
== BCO
);
1115 for (i
= 0; i
< n_payload
; i
++)
1116 pap
->payload
[i
] = (StgClosure
*)Sp
[i
+1];
1118 IF_DEBUG(interpreter
,
1119 debugBelch("\tBuilt ");
1120 printObj((StgClosure
*)pap
);
1126 /* Unpack N ptr words from t.o.s constructor */
1128 int n_words
= BCO_NEXT
;
1129 StgClosure
* con
= (StgClosure
*)Sp
[0];
1131 for (i
= 0; i
< n_words
; i
++) {
1132 Sp
[i
] = (W_
)con
->payload
[i
];
1139 int o_itbl
= BCO_NEXT
;
1140 int n_words
= BCO_NEXT
;
1141 StgInfoTable
* itbl
= INFO_PTR_TO_STRUCT(BCO_LIT(o_itbl
));
1142 int request
= CONSTR_sizeW( itbl
->layout
.payload
.ptrs
,
1143 itbl
->layout
.payload
.nptrs
);
1144 StgClosure
* con
= (StgClosure
*)allocate_NONUPD(request
);
1145 ASSERT( itbl
->layout
.payload
.ptrs
+ itbl
->layout
.payload
.nptrs
> 0);
1146 SET_HDR(con
, (StgInfoTable
*)BCO_LIT(o_itbl
), CCS_SYSTEM
/*ToDo*/);
1147 for (i
= 0; i
< n_words
; i
++) {
1148 con
->payload
[i
] = (StgClosure
*)Sp
[i
];
1153 IF_DEBUG(interpreter
,
1154 debugBelch("\tBuilt ");
1155 printObj((StgClosure
*)con
);
1160 case bci_TESTLT_P
: {
1161 unsigned int discr
= BCO_NEXT
;
1162 int failto
= BCO_NEXT
;
1163 StgClosure
* con
= (StgClosure
*)Sp
[0];
1164 if (GET_TAG(con
) >= discr
) {
1170 case bci_TESTEQ_P
: {
1171 unsigned int discr
= BCO_NEXT
;
1172 int failto
= BCO_NEXT
;
1173 StgClosure
* con
= (StgClosure
*)Sp
[0];
1174 if (GET_TAG(con
) != discr
) {
1180 case bci_TESTLT_I
: {
1181 // There should be an Int at Sp[1], and an info table at Sp[0].
1182 int discr
= BCO_NEXT
;
1183 int failto
= BCO_NEXT
;
1184 I_ stackInt
= (I_
)Sp
[1];
1185 if (stackInt
>= (I_
)BCO_LIT(discr
))
1190 case bci_TESTEQ_I
: {
1191 // There should be an Int at Sp[1], and an info table at Sp[0].
1192 int discr
= BCO_NEXT
;
1193 int failto
= BCO_NEXT
;
1194 I_ stackInt
= (I_
)Sp
[1];
1195 if (stackInt
!= (I_
)BCO_LIT(discr
)) {
1201 case bci_TESTLT_D
: {
1202 // There should be a Double at Sp[1], and an info table at Sp[0].
1203 int discr
= BCO_NEXT
;
1204 int failto
= BCO_NEXT
;
1205 StgDouble stackDbl
, discrDbl
;
1206 stackDbl
= PK_DBL( & Sp
[1] );
1207 discrDbl
= PK_DBL( & BCO_LIT(discr
) );
1208 if (stackDbl
>= discrDbl
) {
1214 case bci_TESTEQ_D
: {
1215 // There should be a Double at Sp[1], and an info table at Sp[0].
1216 int discr
= BCO_NEXT
;
1217 int failto
= BCO_NEXT
;
1218 StgDouble stackDbl
, discrDbl
;
1219 stackDbl
= PK_DBL( & Sp
[1] );
1220 discrDbl
= PK_DBL( & BCO_LIT(discr
) );
1221 if (stackDbl
!= discrDbl
) {
1227 case bci_TESTLT_F
: {
1228 // There should be a Float at Sp[1], and an info table at Sp[0].
1229 int discr
= BCO_NEXT
;
1230 int failto
= BCO_NEXT
;
1231 StgFloat stackFlt
, discrFlt
;
1232 stackFlt
= PK_FLT( & Sp
[1] );
1233 discrFlt
= PK_FLT( & BCO_LIT(discr
) );
1234 if (stackFlt
>= discrFlt
) {
1240 case bci_TESTEQ_F
: {
1241 // There should be a Float at Sp[1], and an info table at Sp[0].
1242 int discr
= BCO_NEXT
;
1243 int failto
= BCO_NEXT
;
1244 StgFloat stackFlt
, discrFlt
;
1245 stackFlt
= PK_FLT( & Sp
[1] );
1246 discrFlt
= PK_FLT( & BCO_LIT(discr
) );
1247 if (stackFlt
!= discrFlt
) {
1253 // Control-flow ish things
1255 // Context-switch check. We put it here to ensure that
1256 // the interpreter has done at least *some* work before
1257 // context switching: sometimes the scheduler can invoke
1258 // the interpreter with context_switch == 1, particularly
1259 // if the -C0 flag has been given on the cmd line.
1260 if (context_switch
) {
1261 Sp
--; Sp
[0] = (W_
)&stg_enter_info
;
1262 RETURN_TO_SCHEDULER(ThreadInterpret
, ThreadYielding
);
1267 obj
= (StgClosure
*)Sp
[0];
1273 Sp
[0] = (W_
)&stg_gc_unpt_r1_info
;
1274 goto do_return_unboxed
;
1277 Sp
[0] = (W_
)&stg_gc_unbx_r1_info
;
1278 goto do_return_unboxed
;
1281 Sp
[0] = (W_
)&stg_gc_f1_info
;
1282 goto do_return_unboxed
;
1285 Sp
[0] = (W_
)&stg_gc_d1_info
;
1286 goto do_return_unboxed
;
1289 Sp
[0] = (W_
)&stg_gc_l1_info
;
1290 goto do_return_unboxed
;
1293 Sp
[0] = (W_
)&stg_gc_void_info
;
1294 goto do_return_unboxed
;
1297 int stkoff
= BCO_NEXT
;
1298 signed short n
= (signed short)(BCO_NEXT
);
1299 Sp
[stkoff
] += (W_
)n
;
1305 int stk_offset
= BCO_NEXT
;
1306 int o_itbl
= BCO_NEXT
;
1307 void(*marshall_fn
)(void*) = (void (*)(void*))BCO_LIT(o_itbl
);
1309 RET_DYN_BITMAP_SIZE
+ RET_DYN_NONPTR_REGS_SIZE
1310 + sizeofW(StgRetDyn
);
1314 // Arguments on the TSO stack are not good, because garbage
1315 // collection might move the TSO as soon as we call
1316 // suspendThread below.
1318 W_ arguments
[stk_offset
];
1320 memcpy(arguments
, Sp
, sizeof(W_
) * stk_offset
);
1323 // Restore the Haskell thread's current value of errno
1324 errno
= cap
->r
.rCurrentTSO
->saved_errno
;
1326 // There are a bunch of non-ptr words on the stack (the
1327 // ccall args, the ccall fun address and space for the
1328 // result), which we need to cover with an info table
1329 // since we might GC during this call.
1331 // We know how many (non-ptr) words there are before the
1332 // next valid stack frame: it is the stk_offset arg to the
1333 // CCALL instruction. So we build a RET_DYN stack frame
1334 // on the stack frame to describe this chunk of stack.
1337 ((StgRetDyn
*)Sp
)->liveness
= NO_PTRS
| N_NONPTRS(stk_offset
);
1338 ((StgRetDyn
*)Sp
)->info
= (StgInfoTable
*)&stg_gc_gen_info
;
1340 SAVE_STACK_POINTERS
;
1341 tok
= suspendThread(&cap
->r
);
1343 #ifndef THREADED_RTS
1345 // suspendThread might have shifted the stack
1346 // around (stack squeezing), so we have to grab the real
1347 // Sp out of the TSO to find the ccall args again.
1349 marshall_fn ( (void*)(cap
->r
.rCurrentTSO
->sp
+ ret_dyn_size
) );
1352 // We already made a copy of the arguments above.
1354 marshall_fn ( arguments
);
1357 // And restart the thread again, popping the RET_DYN frame.
1358 cap
= (Capability
*)((void *)((unsigned char*)resumeThread(tok
) - sizeof(StgFunTable
)));
1359 LOAD_STACK_POINTERS
;
1362 // Save the Haskell thread's current value of errno
1363 cap
->r
.rCurrentTSO
->saved_errno
= errno
;
1367 // Copy the "arguments", which might include a return value,
1368 // back to the TSO stack. It would of course be enough to
1369 // just copy the return value, but we don't know the offset.
1370 memcpy(Sp
, arguments
, sizeof(W_
) * stk_offset
);
1377 /* BCO_NEXT modifies bciPtr, so be conservative. */
1378 int nextpc
= BCO_NEXT
;
1384 barf("interpretBCO: hit a CASEFAIL");
1388 barf("interpretBCO: unknown or unimplemented opcode %d",
1391 } /* switch on opcode */
1395 barf("interpretBCO: fell off end of the interpreter");