1 /* -----------------------------------------------------------------------------
4 * Copyright (c) The GHC Team, 1994-2002.
5 * ---------------------------------------------------------------------------*/
7 #include "PosixSource.h"
15 #include "LdvProfile.h"
20 #include "Bytecodes.h"
22 #include "Disassembler.h"
23 #include "Interpreter.h"
25 #include <string.h> /* for memcpy */
31 /* --------------------------------------------------------------------------
32 * The bytecode interpreter
33 * ------------------------------------------------------------------------*/
35 /* Gather stats about entry, opcode, opcode-pair frequencies. For
36 tuning the interpreter. */
38 /* #define INTERP_STATS */
41 /* Sp points to the lowest live word on the stack. */
43 #define BCO_NEXT instrs[bciPtr++]
44 #define BCO_NEXT_32 (bciPtr += 2, (((StgWord) instrs[bciPtr-2]) << 16) + ((StgWord) instrs[bciPtr-1]))
45 #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]))
46 #if WORD_SIZE_IN_BITS == 32
47 #define BCO_NEXT_WORD BCO_NEXT_32
48 #elif WORD_SIZE_IN_BITS == 64
49 #define BCO_NEXT_WORD BCO_NEXT_64
51 #error Can't cope with WORD_SIZE_IN_BITS being nether 32 nor 64
53 #define BCO_GET_LARGE_ARG ((bci & bci_FLAG_LARGE_ARGS) ? BCO_NEXT_WORD : BCO_NEXT)
55 #define BCO_PTR(n) (W_)ptrs[n]
56 #define BCO_LIT(n) literals[n]
57 #define BCO_ITBL(n) itbls[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
));
90 /* Hacky stats, for tuning the interpreter ... */
91 int it_unknown_entries
[N_CLOSURE_TYPES
];
92 int it_total_unknown_entries
;
104 int it_oofreq
[27][27];
107 #define INTERP_TICK(n) (n)++
109 void interp_startup ( void )
112 it_retto_BCO
= it_retto_UPDATE
= it_retto_other
= 0;
113 it_total_entries
= it_total_unknown_entries
= 0;
114 for (i
= 0; i
< N_CLOSURE_TYPES
; i
++)
115 it_unknown_entries
[i
] = 0;
116 it_slides
= it_insns
= it_BCO_entries
= 0;
117 for (i
= 0; i
< 27; i
++) it_ofreq
[i
] = 0;
118 for (i
= 0; i
< 27; i
++)
119 for (j
= 0; j
< 27; j
++)
124 void interp_shutdown ( void )
126 int i
, j
, k
, o_max
, i_max
, j_max
;
127 debugBelch("%d constrs entered -> (%d BCO, %d UPD, %d ??? )\n",
128 it_retto_BCO
+ it_retto_UPDATE
+ it_retto_other
,
129 it_retto_BCO
, it_retto_UPDATE
, it_retto_other
);
130 debugBelch("%d total entries, %d unknown entries \n",
131 it_total_entries
, it_total_unknown_entries
);
132 for (i
= 0; i
< N_CLOSURE_TYPES
; i
++) {
133 if (it_unknown_entries
[i
] == 0) continue;
134 debugBelch(" type %2d: unknown entries (%4.1f%%) == %d\n",
135 i
, 100.0 * ((double)it_unknown_entries
[i
]) /
136 ((double)it_total_unknown_entries
),
137 it_unknown_entries
[i
]);
139 debugBelch("%d insns, %d slides, %d BCO_entries\n",
140 it_insns
, it_slides
, it_BCO_entries
);
141 for (i
= 0; i
< 27; i
++)
142 debugBelch("opcode %2d got %d\n", i
, it_ofreq
[i
] );
144 for (k
= 1; k
< 20; k
++) {
147 for (i
= 0; i
< 27; i
++) {
148 for (j
= 0; j
< 27; j
++) {
149 if (it_oofreq
[i
][j
] > o_max
) {
150 o_max
= it_oofreq
[i
][j
];
151 i_max
= i
; j_max
= j
;
156 debugBelch("%d: count (%4.1f%%) %6d is %d then %d\n",
157 k
, ((double)o_max
) * 100.0 / ((double)it_insns
), o_max
,
159 it_oofreq
[i_max
][j_max
] = 0;
164 #else // !INTERP_STATS
166 #define INTERP_TICK(n) /* nothing */
170 static StgWord app_ptrs_itbl
[] = {
173 (W_
)&stg_ap_ppp_info
,
174 (W_
)&stg_ap_pppp_info
,
175 (W_
)&stg_ap_ppppp_info
,
176 (W_
)&stg_ap_pppppp_info
,
180 interpretBCO (Capability
* cap
)
182 // Use of register here is primarily to make it clear to compilers
183 // that these entities are non-aliasable.
184 register StgPtr Sp
; // local state -- stack pointer
185 register StgPtr SpLim
; // local state -- stack lim pointer
186 register StgClosure
* obj
;
191 // ------------------------------------------------------------------------
194 // We have a closure to evaluate. Stack looks like:
198 // Sp | -------------------> closure
201 if (Sp
[0] == (W_
)&stg_enter_info
) {
206 // ------------------------------------------------------------------------
209 // We have a BCO application to perform. Stack looks like:
220 else if (Sp
[0] == (W_
)&stg_apply_interp_info
) {
221 obj
= (StgClosure
*)Sp
[1];
226 // ------------------------------------------------------------------------
229 // We have an unboxed value to return. See comment before
230 // do_return_unboxed, below.
233 goto do_return_unboxed
;
236 // Evaluate the object on top of the stack.
238 obj
= (StgClosure
*)Sp
[0]; Sp
++;
241 INTERP_TICK(it_total_evals
);
243 IF_DEBUG(interpreter
,
245 "\n---------------------------------------------------------------\n");
246 debugBelch("Evaluating: "); printObj(obj
);
247 debugBelch("Sp = %p\n", Sp
);
250 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
254 IF_DEBUG(sanity
,checkStackChunk(Sp
, cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
));
256 switch ( get_itbl(obj
)->type
) {
261 case IND_OLDGEN_PERM
:
264 obj
= ((StgInd
*)obj
)->indirectee
;
275 case CONSTR_NOCAF_STATIC
:
288 ASSERT(((StgBCO
*)obj
)->arity
> 0);
291 case AP
: /* Copied from stg_AP_entry. */
300 if (Sp
- (words
+sizeofW(StgUpdateFrame
)) < SpLim
) {
303 Sp
[0] = (W_
)&stg_enter_info
;
304 RETURN_TO_SCHEDULER(ThreadInterpret
, StackOverflow
);
307 /* Ok; we're safe. Party on. Push an update frame. */
308 Sp
-= sizeofW(StgUpdateFrame
);
310 StgUpdateFrame
*__frame
;
311 __frame
= (StgUpdateFrame
*)Sp
;
312 SET_INFO(__frame
, (StgInfoTable
*)&stg_upd_frame_info
);
313 __frame
->updatee
= (StgClosure
*)(ap
);
316 /* Reload the stack */
318 for (i
=0; i
< words
; i
++) {
319 Sp
[i
] = (W_
)ap
->payload
[i
];
322 obj
= (StgClosure
*)ap
->fun
;
323 ASSERT(get_itbl(obj
)->type
== BCO
);
332 j
= get_itbl(obj
)->type
;
333 ASSERT(j
>= 0 && j
< N_CLOSURE_TYPES
);
334 it_unknown_entries
[j
]++;
335 it_total_unknown_entries
++;
339 // Can't handle this object; yield to scheduler
340 IF_DEBUG(interpreter
,
341 debugBelch("evaluating unknown closure -- yielding to sched\n");
346 Sp
[0] = (W_
)&stg_enter_info
;
347 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
351 // ------------------------------------------------------------------------
352 // We now have an evaluated object (obj). The next thing to
353 // do is return it to the stack frame on top of the stack.
355 ASSERT(closure_HNF(obj
));
357 IF_DEBUG(interpreter
,
359 "\n---------------------------------------------------------------\n");
360 debugBelch("Returning: "); printObj(obj
);
361 debugBelch("Sp = %p\n", Sp
);
363 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
367 IF_DEBUG(sanity
,checkStackChunk(Sp
, cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
));
369 switch (get_itbl((StgClosure
*)Sp
)->type
) {
372 const StgInfoTable
*info
;
374 // NOTE: not using get_itbl().
375 info
= ((StgClosure
*)Sp
)->header
.info
;
376 if (info
== (StgInfoTable
*)&stg_ap_v_info
) {
377 n
= 1; m
= 0; goto do_apply
;
379 if (info
== (StgInfoTable
*)&stg_ap_f_info
) {
380 n
= 1; m
= 1; goto do_apply
;
382 if (info
== (StgInfoTable
*)&stg_ap_d_info
) {
383 n
= 1; m
= sizeofW(StgDouble
); goto do_apply
;
385 if (info
== (StgInfoTable
*)&stg_ap_l_info
) {
386 n
= 1; m
= sizeofW(StgInt64
); goto do_apply
;
388 if (info
== (StgInfoTable
*)&stg_ap_n_info
) {
389 n
= 1; m
= 1; goto do_apply
;
391 if (info
== (StgInfoTable
*)&stg_ap_p_info
) {
392 n
= 1; m
= 1; goto do_apply
;
394 if (info
== (StgInfoTable
*)&stg_ap_pp_info
) {
395 n
= 2; m
= 2; goto do_apply
;
397 if (info
== (StgInfoTable
*)&stg_ap_ppp_info
) {
398 n
= 3; m
= 3; goto do_apply
;
400 if (info
== (StgInfoTable
*)&stg_ap_pppp_info
) {
401 n
= 4; m
= 4; goto do_apply
;
403 if (info
== (StgInfoTable
*)&stg_ap_ppppp_info
) {
404 n
= 5; m
= 5; goto do_apply
;
406 if (info
== (StgInfoTable
*)&stg_ap_pppppp_info
) {
407 n
= 6; m
= 6; goto do_apply
;
409 goto do_return_unrecognised
;
413 // Returning to an update frame: do the update, pop the update
414 // frame, and continue with the next stack frame.
415 INTERP_TICK(it_retto_UPDATE
);
416 UPD_IND(((StgUpdateFrame
*)Sp
)->updatee
, obj
);
417 Sp
+= sizeofW(StgUpdateFrame
);
421 // Returning to an interpreted continuation: put the object on
422 // the stack, and start executing the BCO.
423 INTERP_TICK(it_retto_BCO
);
426 obj
= (StgClosure
*)Sp
[2];
427 ASSERT(get_itbl(obj
)->type
== BCO
);
431 do_return_unrecognised
:
433 // Can't handle this return address; yield to scheduler
434 INTERP_TICK(it_retto_other
);
435 IF_DEBUG(interpreter
,
436 debugBelch("returning to unknown frame -- yielding to sched\n");
437 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
441 Sp
[0] = (W_
)&stg_enter_info
;
442 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
446 // -------------------------------------------------------------------------
447 // Returning an unboxed value. The stack looks like this:
464 // where XXXX_info is one of the stg_gc_unbx_r1_info family.
466 // We're only interested in the case when the real return address
467 // is a BCO; otherwise we'll return to the scheduler.
473 ASSERT( Sp
[0] == (W_
)&stg_gc_unbx_r1_info
474 || Sp
[0] == (W_
)&stg_gc_unpt_r1_info
475 || Sp
[0] == (W_
)&stg_gc_f1_info
476 || Sp
[0] == (W_
)&stg_gc_d1_info
477 || Sp
[0] == (W_
)&stg_gc_l1_info
478 || Sp
[0] == (W_
)&stg_gc_void_info
// VoidRep
481 // get the offset of the stg_ctoi_ret_XXX itbl
482 offset
= stack_frame_sizeW((StgClosure
*)Sp
);
484 switch (get_itbl((StgClosure
*)Sp
+offset
)->type
) {
487 // Returning to an interpreted continuation: put the object on
488 // the stack, and start executing the BCO.
489 INTERP_TICK(it_retto_BCO
);
490 obj
= (StgClosure
*)Sp
[offset
+1];
491 ASSERT(get_itbl(obj
)->type
== BCO
);
492 goto run_BCO_return_unboxed
;
496 // Can't handle this return address; yield to scheduler
497 INTERP_TICK(it_retto_other
);
498 IF_DEBUG(interpreter
,
499 debugBelch("returning to unknown frame -- yielding to sched\n");
500 printStackChunk(Sp
,cap
->r
.rCurrentTSO
->stack
+cap
->r
.rCurrentTSO
->stack_size
);
502 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
509 // -------------------------------------------------------------------------
513 // we have a function to apply (obj), and n arguments taking up m
514 // words on the stack. The info table (stg_ap_pp_info or whatever)
515 // is on top of the arguments on the stack.
517 switch (get_itbl(obj
)->type
) {
525 // we only cope with PAPs whose function is a BCO
526 if (get_itbl(pap
->fun
)->type
!= BCO
) {
527 goto defer_apply_to_sched
;
534 // n must be greater than 1, and the only kinds of
535 // application we support with more than one argument
536 // are all pointers...
538 // Shuffle the args for this function down, and put
539 // the appropriate info table in the gap.
540 for (i
= 0; i
< arity
; i
++) {
541 Sp
[(int)i
-1] = Sp
[i
];
542 // ^^^^^ careful, i-1 might be negative, but i in unsigned
544 Sp
[arity
-1] = app_ptrs_itbl
[n
-arity
-1];
546 // unpack the PAP's arguments onto the stack
548 for (i
= 0; i
< pap
->n_args
; i
++) {
549 Sp
[i
] = (W_
)pap
->payload
[i
];
554 else if (arity
== n
) {
556 for (i
= 0; i
< pap
->n_args
; i
++) {
557 Sp
[i
] = (W_
)pap
->payload
[i
];
562 else /* arity > n */ {
563 // build a new PAP and return it.
565 new_pap
= (StgPAP
*)allocate(PAP_sizeW(pap
->n_args
+ m
));
566 SET_HDR(new_pap
,&stg_PAP_info
,CCCS
);
567 new_pap
->arity
= pap
->arity
- n
;
568 new_pap
->n_args
= pap
->n_args
+ m
;
569 new_pap
->fun
= pap
->fun
;
570 for (i
= 0; i
< pap
->n_args
; i
++) {
571 new_pap
->payload
[i
] = pap
->payload
[i
];
573 for (i
= 0; i
< m
; i
++) {
574 new_pap
->payload
[pap
->n_args
+ i
] = (StgClosure
*)Sp
[i
];
576 obj
= (StgClosure
*)new_pap
;
586 arity
= ((StgBCO
*)obj
)->arity
;
589 // n must be greater than 1, and the only kinds of
590 // application we support with more than one argument
591 // are all pointers...
593 // Shuffle the args for this function down, and put
594 // the appropriate info table in the gap.
595 for (i
= 0; i
< arity
; i
++) {
596 Sp
[(int)i
-1] = Sp
[i
];
597 // ^^^^^ careful, i-1 might be negative, but i in unsigned
599 Sp
[arity
-1] = app_ptrs_itbl
[n
-arity
-1];
603 else if (arity
== n
) {
606 else /* arity > n */ {
607 // build a PAP and return it.
610 pap
= (StgPAP
*)allocate(PAP_sizeW(m
));
611 SET_HDR(pap
, &stg_PAP_info
,CCCS
);
612 pap
->arity
= arity
- n
;
615 for (i
= 0; i
< m
; i
++) {
616 pap
->payload
[i
] = (StgClosure
*)Sp
[i
];
618 obj
= (StgClosure
*)pap
;
624 // No point in us applying machine-code functions
626 defer_apply_to_sched
:
629 Sp
[0] = (W_
)&stg_enter_info
;
630 RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC
, ThreadYielding
);
633 // ------------------------------------------------------------------------
634 // Ok, we now have a bco (obj), and its arguments are all on the
635 // stack. We can start executing the byte codes.
637 // The stack is in one of two states. First, if this BCO is a
647 // Second, if this BCO is a continuation:
662 // where retval is the value being returned to this continuation.
663 // In the event of a stack check, heap check, or context switch,
664 // we need to leave the stack in a sane state so the garbage
665 // collector can find all the pointers.
667 // (1) BCO is a function: the BCO's bitmap describes the
668 // pointerhood of the arguments.
670 // (2) BCO is a continuation: BCO's bitmap describes the
671 // pointerhood of the free variables.
673 // Sadly we have three different kinds of stack/heap/cswitch check
678 if (doYouWantToGC()) {
679 Sp
--; Sp
[0] = (W_
)&stg_enter_info
;
680 RETURN_TO_SCHEDULER(ThreadInterpret
, HeapOverflow
);
682 // Stack checks aren't necessary at return points, the stack use
683 // is aggregated into the enclosing function entry point.
686 run_BCO_return_unboxed
:
688 if (doYouWantToGC()) {
689 RETURN_TO_SCHEDULER(ThreadInterpret
, HeapOverflow
);
691 // Stack checks aren't necessary at return points, the stack use
692 // is aggregated into the enclosing function entry point.
699 Sp
[0] = (W_
)&stg_apply_interp_info
;
700 checkStackChunk(Sp
,SpLim
);
705 if (doYouWantToGC()) {
708 Sp
[0] = (W_
)&stg_apply_interp_info
; // placeholder, really
709 RETURN_TO_SCHEDULER(ThreadInterpret
, HeapOverflow
);
713 if (Sp
- INTERP_STACK_CHECK_THRESH
< SpLim
) {
716 Sp
[0] = (W_
)&stg_apply_interp_info
; // placeholder, really
717 RETURN_TO_SCHEDULER(ThreadInterpret
, StackOverflow
);
721 // Now, actually interpret the BCO... (no returning to the
722 // scheduler again until the stack is in an orderly state).
724 INTERP_TICK(it_BCO_entries
);
726 register int bciPtr
= 1; /* instruction pointer */
727 register StgWord16 bci
;
728 register StgBCO
* bco
= (StgBCO
*)obj
;
729 register StgWord16
* instrs
= (StgWord16
*)(bco
->instrs
->payload
);
730 register StgWord
* literals
= (StgWord
*)(&bco
->literals
->payload
[0]);
731 register StgPtr
* ptrs
= (StgPtr
*)(&bco
->ptrs
->payload
[0]);
732 register StgInfoTable
** itbls
= (StgInfoTable
**)
733 (&bco
->itbls
->payload
[0]);
736 it_lastopc
= 0; /* no opcode */
740 ASSERT(bciPtr
<= instrs
[0]);
741 IF_DEBUG(interpreter
,
742 //if (do_print_stack) {
743 //debugBelch("\n-- BEGIN stack\n");
744 //printStack(Sp,cap->r.rCurrentTSO->stack+cap->r.rCurrentTSO->stack_size,iSu);
745 //debugBelch("-- END stack\n\n");
747 debugBelch("Sp = %p pc = %d ", Sp
, bciPtr
);
748 disInstr(bco
,bciPtr
);
751 for (i
= 8; i
>= 0; i
--) {
752 debugBelch("%d %p\n", i
, (StgPtr
)(*(Sp
+i
)));
756 //if (do_print_stack) checkStack(Sp,cap->r.rCurrentTSO->stack+cap->r.rCurrentTSO->stack_size,iSu);
759 INTERP_TICK(it_insns
);
762 ASSERT( (int)instrs
[bciPtr
] >= 0 && (int)instrs
[bciPtr
] < 27 );
763 it_ofreq
[ (int)instrs
[bciPtr
] ] ++;
764 it_oofreq
[ it_lastopc
][ (int)instrs
[bciPtr
] ] ++;
765 it_lastopc
= (int)instrs
[bciPtr
];
769 /* We use the high 8 bits for flags, only the highest of which is
770 * currently allocated */
771 ASSERT((bci
& 0xFF00) == (bci
& 0x8000));
773 switch (bci
& 0xFF) {
776 // Explicit stack check at the beginning of a function
777 // *only* (stack checks in case alternatives are
778 // propagated to the enclosing function).
779 StgWord stk_words_reqd
= BCO_GET_LARGE_ARG
+ 1;
780 if (Sp
- stk_words_reqd
< SpLim
) {
783 Sp
[0] = (W_
)&stg_apply_interp_info
;
784 RETURN_TO_SCHEDULER(ThreadInterpret
, StackOverflow
);
819 Sp
[-1] = BCO_PTR(o1
);
824 case bci_PUSH_ALTS
: {
825 int o_bco
= BCO_NEXT
;
826 Sp
[-2] = (W_
)&stg_ctoi_R1p_info
;
827 Sp
[-1] = BCO_PTR(o_bco
);
832 case bci_PUSH_ALTS_P
: {
833 int o_bco
= BCO_NEXT
;
834 Sp
[-2] = (W_
)&stg_ctoi_R1unpt_info
;
835 Sp
[-1] = BCO_PTR(o_bco
);
840 case bci_PUSH_ALTS_N
: {
841 int o_bco
= BCO_NEXT
;
842 Sp
[-2] = (W_
)&stg_ctoi_R1n_info
;
843 Sp
[-1] = BCO_PTR(o_bco
);
848 case bci_PUSH_ALTS_F
: {
849 int o_bco
= BCO_NEXT
;
850 Sp
[-2] = (W_
)&stg_ctoi_F1_info
;
851 Sp
[-1] = BCO_PTR(o_bco
);
856 case bci_PUSH_ALTS_D
: {
857 int o_bco
= BCO_NEXT
;
858 Sp
[-2] = (W_
)&stg_ctoi_D1_info
;
859 Sp
[-1] = BCO_PTR(o_bco
);
864 case bci_PUSH_ALTS_L
: {
865 int o_bco
= BCO_NEXT
;
866 Sp
[-2] = (W_
)&stg_ctoi_L1_info
;
867 Sp
[-1] = BCO_PTR(o_bco
);
872 case bci_PUSH_ALTS_V
: {
873 int o_bco
= BCO_NEXT
;
874 Sp
[-2] = (W_
)&stg_ctoi_V_info
;
875 Sp
[-1] = BCO_PTR(o_bco
);
880 case bci_PUSH_APPLY_N
:
881 Sp
--; Sp
[0] = (W_
)&stg_ap_n_info
;
883 case bci_PUSH_APPLY_V
:
884 Sp
--; Sp
[0] = (W_
)&stg_ap_v_info
;
886 case bci_PUSH_APPLY_F
:
887 Sp
--; Sp
[0] = (W_
)&stg_ap_f_info
;
889 case bci_PUSH_APPLY_D
:
890 Sp
--; Sp
[0] = (W_
)&stg_ap_d_info
;
892 case bci_PUSH_APPLY_L
:
893 Sp
--; Sp
[0] = (W_
)&stg_ap_l_info
;
895 case bci_PUSH_APPLY_P
:
896 Sp
--; Sp
[0] = (W_
)&stg_ap_p_info
;
898 case bci_PUSH_APPLY_PP
:
899 Sp
--; Sp
[0] = (W_
)&stg_ap_pp_info
;
901 case bci_PUSH_APPLY_PPP
:
902 Sp
--; Sp
[0] = (W_
)&stg_ap_ppp_info
;
904 case bci_PUSH_APPLY_PPPP
:
905 Sp
--; Sp
[0] = (W_
)&stg_ap_pppp_info
;
907 case bci_PUSH_APPLY_PPPPP
:
908 Sp
--; Sp
[0] = (W_
)&stg_ap_ppppp_info
;
910 case bci_PUSH_APPLY_PPPPPP
:
911 Sp
--; Sp
[0] = (W_
)&stg_ap_pppppp_info
;
916 int o_lits
= BCO_NEXT
;
917 int n_words
= BCO_NEXT
;
919 for (i
= 0; i
< n_words
; i
++) {
920 Sp
[i
] = (W_
)BCO_LIT(o_lits
+i
);
928 /* a_1, .. a_n, b_1, .. b_by, s => a_1, .. a_n, s */
933 INTERP_TICK(it_slides
);
939 int n_payload
= BCO_NEXT
;
940 ap
= (StgAP
*)allocate(AP_sizeW(n_payload
));
942 ap
->n_args
= n_payload
;
943 SET_HDR(ap
, &stg_AP_info
, CCS_SYSTEM
/*ToDo*/)
948 case bci_ALLOC_PAP
: {
950 int arity
= BCO_NEXT
;
951 int n_payload
= BCO_NEXT
;
952 pap
= (StgPAP
*)allocate(PAP_sizeW(n_payload
));
954 pap
->n_args
= n_payload
;
956 SET_HDR(pap
, &stg_PAP_info
, CCS_SYSTEM
/*ToDo*/)
963 int stkoff
= BCO_NEXT
;
964 int n_payload
= BCO_NEXT
;
965 StgAP
* ap
= (StgAP
*)Sp
[stkoff
];
966 ASSERT((int)ap
->n_args
== n_payload
);
967 ap
->fun
= (StgClosure
*)Sp
[0];
969 // The function should be a BCO, and its bitmap should
970 // cover the payload of the AP correctly.
971 ASSERT(get_itbl(ap
->fun
)->type
== BCO
972 && BCO_BITMAP_SIZE(ap
->fun
) == ap
->n_args
);
974 for (i
= 0; i
< n_payload
; i
++)
975 ap
->payload
[i
] = (StgClosure
*)Sp
[i
+1];
977 IF_DEBUG(interpreter
,
978 debugBelch("\tBuilt ");
979 printObj((StgClosure
*)ap
);
986 int stkoff
= BCO_NEXT
;
987 int n_payload
= BCO_NEXT
;
988 StgPAP
* pap
= (StgPAP
*)Sp
[stkoff
];
989 ASSERT((int)pap
->n_args
== n_payload
);
990 pap
->fun
= (StgClosure
*)Sp
[0];
992 // The function should be a BCO
993 ASSERT(get_itbl(pap
->fun
)->type
== BCO
);
995 for (i
= 0; i
< n_payload
; i
++)
996 pap
->payload
[i
] = (StgClosure
*)Sp
[i
+1];
998 IF_DEBUG(interpreter
,
999 debugBelch("\tBuilt ");
1000 printObj((StgClosure
*)pap
);
1006 /* Unpack N ptr words from t.o.s constructor */
1008 int n_words
= BCO_NEXT
;
1009 StgClosure
* con
= (StgClosure
*)Sp
[0];
1011 for (i
= 0; i
< n_words
; i
++) {
1012 Sp
[i
] = (W_
)con
->payload
[i
];
1019 int o_itbl
= BCO_NEXT
;
1020 int n_words
= BCO_NEXT
;
1021 StgInfoTable
* itbl
= INFO_PTR_TO_STRUCT(BCO_ITBL(o_itbl
));
1022 int request
= CONSTR_sizeW( itbl
->layout
.payload
.ptrs
,
1023 itbl
->layout
.payload
.nptrs
);
1024 StgClosure
* con
= (StgClosure
*)allocate_NONUPD(request
);
1025 ASSERT( itbl
->layout
.payload
.ptrs
+ itbl
->layout
.payload
.nptrs
> 0);
1026 SET_HDR(con
, BCO_ITBL(o_itbl
), CCS_SYSTEM
/*ToDo*/);
1027 for (i
= 0; i
< n_words
; i
++) {
1028 con
->payload
[i
] = (StgClosure
*)Sp
[i
];
1033 IF_DEBUG(interpreter
,
1034 debugBelch("\tBuilt ");
1035 printObj((StgClosure
*)con
);
1040 case bci_TESTLT_P
: {
1041 unsigned int discr
= BCO_NEXT
;
1042 int failto
= BCO_NEXT
;
1043 StgClosure
* con
= (StgClosure
*)Sp
[0];
1044 if (GET_TAG(con
) >= discr
) {
1050 case bci_TESTEQ_P
: {
1051 unsigned int discr
= BCO_NEXT
;
1052 int failto
= BCO_NEXT
;
1053 StgClosure
* con
= (StgClosure
*)Sp
[0];
1054 if (GET_TAG(con
) != discr
) {
1060 case bci_TESTLT_I
: {
1061 // There should be an Int at Sp[1], and an info table at Sp[0].
1062 int discr
= BCO_NEXT
;
1063 int failto
= BCO_NEXT
;
1064 I_ stackInt
= (I_
)Sp
[1];
1065 if (stackInt
>= (I_
)BCO_LIT(discr
))
1070 case bci_TESTEQ_I
: {
1071 // There should be an Int at Sp[1], and an info table at Sp[0].
1072 int discr
= BCO_NEXT
;
1073 int failto
= BCO_NEXT
;
1074 I_ stackInt
= (I_
)Sp
[1];
1075 if (stackInt
!= (I_
)BCO_LIT(discr
)) {
1081 case bci_TESTLT_D
: {
1082 // There should be a Double at Sp[1], and an info table at Sp[0].
1083 int discr
= BCO_NEXT
;
1084 int failto
= BCO_NEXT
;
1085 StgDouble stackDbl
, discrDbl
;
1086 stackDbl
= PK_DBL( & Sp
[1] );
1087 discrDbl
= PK_DBL( & BCO_LIT(discr
) );
1088 if (stackDbl
>= discrDbl
) {
1094 case bci_TESTEQ_D
: {
1095 // There should be a Double at Sp[1], and an info table at Sp[0].
1096 int discr
= BCO_NEXT
;
1097 int failto
= BCO_NEXT
;
1098 StgDouble stackDbl
, discrDbl
;
1099 stackDbl
= PK_DBL( & Sp
[1] );
1100 discrDbl
= PK_DBL( & BCO_LIT(discr
) );
1101 if (stackDbl
!= discrDbl
) {
1107 case bci_TESTLT_F
: {
1108 // There should be a Float at Sp[1], and an info table at Sp[0].
1109 int discr
= BCO_NEXT
;
1110 int failto
= BCO_NEXT
;
1111 StgFloat stackFlt
, discrFlt
;
1112 stackFlt
= PK_FLT( & Sp
[1] );
1113 discrFlt
= PK_FLT( & BCO_LIT(discr
) );
1114 if (stackFlt
>= discrFlt
) {
1120 case bci_TESTEQ_F
: {
1121 // There should be a Float at Sp[1], and an info table at Sp[0].
1122 int discr
= BCO_NEXT
;
1123 int failto
= BCO_NEXT
;
1124 StgFloat stackFlt
, discrFlt
;
1125 stackFlt
= PK_FLT( & Sp
[1] );
1126 discrFlt
= PK_FLT( & BCO_LIT(discr
) );
1127 if (stackFlt
!= discrFlt
) {
1133 // Control-flow ish things
1135 // Context-switch check. We put it here to ensure that
1136 // the interpreter has done at least *some* work before
1137 // context switching: sometimes the scheduler can invoke
1138 // the interpreter with context_switch == 1, particularly
1139 // if the -C0 flag has been given on the cmd line.
1140 if (context_switch
) {
1141 Sp
--; Sp
[0] = (W_
)&stg_enter_info
;
1142 RETURN_TO_SCHEDULER(ThreadInterpret
, ThreadYielding
);
1147 obj
= (StgClosure
*)Sp
[0];
1153 Sp
[0] = (W_
)&stg_gc_unpt_r1_info
;
1154 goto do_return_unboxed
;
1157 Sp
[0] = (W_
)&stg_gc_unbx_r1_info
;
1158 goto do_return_unboxed
;
1161 Sp
[0] = (W_
)&stg_gc_f1_info
;
1162 goto do_return_unboxed
;
1165 Sp
[0] = (W_
)&stg_gc_d1_info
;
1166 goto do_return_unboxed
;
1169 Sp
[0] = (W_
)&stg_gc_l1_info
;
1170 goto do_return_unboxed
;
1173 Sp
[0] = (W_
)&stg_gc_void_info
;
1174 goto do_return_unboxed
;
1177 int stkoff
= BCO_NEXT
;
1178 signed short n
= (signed short)(BCO_NEXT
);
1179 Sp
[stkoff
] += (W_
)n
;
1185 int stk_offset
= BCO_NEXT
;
1186 int o_itbl
= BCO_NEXT
;
1187 void(*marshall_fn
)(void*) = (void (*)(void*))BCO_LIT(o_itbl
);
1189 RET_DYN_BITMAP_SIZE
+ RET_DYN_NONPTR_REGS_SIZE
1190 + sizeofW(StgRetDyn
);
1194 // Arguments on the TSO stack are not good, because garbage
1195 // collection might move the TSO as soon as we call
1196 // suspendThread below.
1198 W_ arguments
[stk_offset
];
1200 memcpy(arguments
, Sp
, sizeof(W_
) * stk_offset
);
1203 // Restore the Haskell thread's current value of errno
1204 errno
= cap
->r
.rCurrentTSO
->saved_errno
;
1206 // There are a bunch of non-ptr words on the stack (the
1207 // ccall args, the ccall fun address and space for the
1208 // result), which we need to cover with an info table
1209 // since we might GC during this call.
1211 // We know how many (non-ptr) words there are before the
1212 // next valid stack frame: it is the stk_offset arg to the
1213 // CCALL instruction. So we build a RET_DYN stack frame
1214 // on the stack frame to describe this chunk of stack.
1217 ((StgRetDyn
*)Sp
)->liveness
= NO_PTRS
| N_NONPTRS(stk_offset
);
1218 ((StgRetDyn
*)Sp
)->info
= (StgInfoTable
*)&stg_gc_gen_info
;
1220 SAVE_STACK_POINTERS
;
1221 tok
= suspendThread(&cap
->r
);
1223 #ifndef THREADED_RTS
1225 // suspendThread might have shifted the stack
1226 // around (stack squeezing), so we have to grab the real
1227 // Sp out of the TSO to find the ccall args again.
1229 marshall_fn ( (void*)(cap
->r
.rCurrentTSO
->sp
+ ret_dyn_size
) );
1232 // We already made a copy of the arguments above.
1234 marshall_fn ( arguments
);
1237 // And restart the thread again, popping the RET_DYN frame.
1238 cap
= (Capability
*)((void *)((unsigned char*)resumeThread(tok
) - sizeof(StgFunTable
)));
1239 LOAD_STACK_POINTERS
;
1242 // Save the Haskell thread's current value of errno
1243 cap
->r
.rCurrentTSO
->saved_errno
= errno
;
1247 // Copy the "arguments", which might include a return value,
1248 // back to the TSO stack. It would of course be enough to
1249 // just copy the return value, but we don't know the offset.
1250 memcpy(Sp
, arguments
, sizeof(W_
) * stk_offset
);
1257 /* BCO_NEXT modifies bciPtr, so be conservative. */
1258 int nextpc
= BCO_NEXT
;
1264 barf("interpretBCO: hit a CASEFAIL");
1268 barf("interpretBCO: unknown or unimplemented opcode %d",
1271 } /* switch on opcode */
1275 barf("interpretBCO: fell off end of the interpreter");