]> gitweb.factorcode.org Git - factor.git/blob - basis/cpu/x86/x86.factor
Various improvements aimed at getting local optimization regressions fixed:
[factor.git] / basis / cpu / x86 / x86.factor
1 ! Copyright (C) 2005, 2008 Slava Pestov.
2 ! See http://factorcode.org/license.txt for BSD license.
3 USING: accessors assocs alien alien.c-types arrays strings
4 cpu.x86.assembler cpu.x86.assembler.private cpu.architecture
5 kernel kernel.private math memory namespaces make sequences
6 words system layouts combinators math.order fry locals
7 compiler.constants compiler.cfg.registers
8 compiler.cfg.instructions compiler.cfg.intrinsics
9 compiler.codegen compiler.codegen.fixup ;
10 IN: cpu.x86
11
12 << enable-fixnum-log2 >>
13
14 ! Add some methods to the assembler to be more useful to the backend
15 M: label JMP 0 JMP rc-relative label-fixup ;
16 M: label JUMPcc [ 0 ] dip JUMPcc rc-relative label-fixup ;
17
18 M: x86 two-operand? t ;
19
20 HOOK: temp-reg-1 cpu ( -- reg )
21 HOOK: temp-reg-2 cpu ( -- reg )
22
23 HOOK: param-reg-1 cpu ( -- reg )
24 HOOK: param-reg-2 cpu ( -- reg )
25
26 HOOK: pic-tail-reg cpu ( -- reg )
27
28 M: x86 %load-immediate MOV ;
29
30 M: x86 %load-reference swap 0 MOV rc-absolute-cell rel-immediate ;
31
32 HOOK: ds-reg cpu ( -- reg )
33 HOOK: rs-reg cpu ( -- reg )
34
35 : reg-stack ( n reg -- op ) swap cells neg [+] ;
36
37 GENERIC: loc>operand ( loc -- operand )
38
39 M: ds-loc loc>operand n>> ds-reg reg-stack ;
40 M: rs-loc loc>operand n>> rs-reg reg-stack ;
41
42 M: x86 %peek loc>operand MOV ;
43 M: x86 %replace loc>operand swap MOV ;
44 : (%inc) ( n reg -- ) swap cells dup 0 > [ ADD ] [ neg SUB ] if ; inline
45 M: x86 %inc-d ( n -- ) ds-reg (%inc) ;
46 M: x86 %inc-r ( n -- ) rs-reg (%inc) ;
47
48 : align-stack ( n -- n' )
49     os macosx? cpu x86.64? or [ 16 align ] when ;
50
51 HOOK: reserved-area-size cpu ( -- n )
52
53 M: x86 stack-frame-size ( stack-frame -- i )
54     [ spill-counts>> [ swap reg-size * ] { } assoc>map sum ]
55     [ params>> ]
56     [ return>> ]
57     tri + +
58     3 cells +
59     reserved-area-size +
60     align-stack ;
61
62 M: x86 %call ( word -- ) 0 CALL rc-relative rel-word-pic ;
63
64 : xt-tail-pic-offset ( -- n )
65     #! See the comment in vm/cpu-x86.hpp
66     cell 4 + 1 + ; inline
67
68 M: x86 %jump ( word -- )
69     pic-tail-reg 0 MOV xt-tail-pic-offset rc-absolute-cell rel-here
70     0 JMP rc-relative rel-word-pic-tail ;
71
72 M: x86 %jump-label ( label -- ) 0 JMP rc-relative label-fixup ;
73
74 M: x86 %return ( -- ) 0 RET ;
75
76 : code-alignment ( align -- n )
77     [ building get [ integer? ] count dup ] dip align swap - ;
78
79 : align-code ( n -- )
80     0 <repetition> % ;
81
82 M: x86 %dispatch-label ( label -- )
83     0 cell, rc-absolute-cell label-fixup ;
84
85 :: (%slot) ( obj slot tag temp -- op )
86     temp slot obj [+] LEA
87     temp tag neg [+] ; inline
88
89 :: (%slot-imm) ( obj slot tag -- op )
90     obj slot cells tag - [+] ; inline
91
92 M: x86 %slot ( dst obj slot tag temp -- ) (%slot) MOV ;
93 M: x86 %slot-imm ( dst obj slot tag -- ) (%slot-imm) MOV ;
94 M: x86 %set-slot ( src obj slot tag temp -- ) (%slot) swap MOV ;
95 M: x86 %set-slot-imm ( src obj slot tag -- ) (%slot-imm) swap MOV ;
96
97 M: x86 %add     [+] LEA ;
98 M: x86 %add-imm [+] LEA ;
99 M: x86 %sub     nip SUB ;
100 M: x86 %sub-imm neg [+] LEA ;
101 M: x86 %mul     nip swap IMUL2 ;
102 M: x86 %mul-imm nip IMUL2 ;
103 M: x86 %and     nip AND ;
104 M: x86 %and-imm nip AND ;
105 M: x86 %or      nip OR ;
106 M: x86 %or-imm  nip OR ;
107 M: x86 %xor     nip XOR ;
108 M: x86 %xor-imm nip XOR ;
109 M: x86 %shl-imm nip SHL ;
110 M: x86 %shr-imm nip SHR ;
111 M: x86 %sar-imm nip SAR ;
112 M: x86 %not     drop NOT ;
113 M: x86 %log2    BSR ;
114
115 : ?MOV ( dst src -- )
116     2dup = [ 2drop ] [ MOV ] if ; inline
117
118 :: move>args ( src1 src2 -- )
119     {
120         { [ src1 param-reg-2 = ] [ param-reg-1 src2 ?MOV param-reg-1 param-reg-2 XCHG ] }
121         { [ src1 param-reg-1 = ] [ param-reg-2 src2 ?MOV ] }
122         { [ src2 param-reg-1 = ] [ param-reg-2 src1 ?MOV param-reg-1 param-reg-2 XCHG ] }
123         { [ src2 param-reg-2 = ] [ param-reg-1 src1 ?MOV ] }
124         [
125             param-reg-1 src1 MOV
126             param-reg-2 src2 MOV
127         ]
128     } cond ;
129
130 HOOK: %alien-invoke-tail cpu ( func dll -- )
131
132 :: overflow-template ( src1 src2 insn inverse func -- )
133     <label> "no-overflow" set
134     src1 src2 insn call
135     ds-reg [] src1 MOV
136     "no-overflow" get JNO
137     src1 src2 inverse call
138     src1 src2 move>args
139     %prepare-alien-invoke
140     func f %alien-invoke
141     "no-overflow" resolve-label ; inline
142
143 :: overflow-template-tail ( src1 src2 insn inverse func -- )
144     <label> "no-overflow" set
145     src1 src2 insn call
146     "no-overflow" get JNO
147     src1 src2 inverse call
148     src1 src2 move>args
149     %prepare-alien-invoke
150     func f %alien-invoke-tail
151     "no-overflow" resolve-label
152     ds-reg [] src1 MOV
153     0 RET ; inline
154
155 M: x86 %fixnum-add ( src1 src2 -- )
156     [ ADD ] [ SUB ] "overflow_fixnum_add" overflow-template ;
157
158 M: x86 %fixnum-add-tail ( src1 src2 -- )
159     [ ADD ] [ SUB ] "overflow_fixnum_add" overflow-template-tail ;
160
161 M: x86 %fixnum-sub ( src1 src2 -- )
162     [ SUB ] [ ADD ] "overflow_fixnum_subtract" overflow-template ;
163
164 M: x86 %fixnum-sub-tail ( src1 src2 -- )
165     [ SUB ] [ ADD ] "overflow_fixnum_subtract" overflow-template-tail ;
166
167 M:: x86 %fixnum-mul ( src1 src2 temp1 temp2 -- )
168     "no-overflow" define-label
169     temp1 src1 MOV
170     temp1 tag-bits get SAR
171     src2 temp1 IMUL2
172     ds-reg [] temp1 MOV
173     "no-overflow" get JNO
174     src1 src2 move>args
175     param-reg-1 tag-bits get SAR
176     param-reg-2 tag-bits get SAR
177     %prepare-alien-invoke
178     "overflow_fixnum_multiply" f %alien-invoke
179     "no-overflow" resolve-label ;
180
181 M:: x86 %fixnum-mul-tail ( src1 src2 temp1 temp2 -- )
182     "overflow" define-label
183     temp1 src1 MOV
184     temp1 tag-bits get SAR
185     src2 temp1 IMUL2
186     "overflow" get JO
187     ds-reg [] temp1 MOV
188     0 RET
189     "overflow" resolve-label
190     src1 src2 move>args
191     param-reg-1 tag-bits get SAR
192     param-reg-2 tag-bits get SAR
193     %prepare-alien-invoke
194     "overflow_fixnum_multiply" f %alien-invoke-tail ;
195
196 : bignum@ ( reg n -- op )
197     cells bignum tag-number - [+] ; inline
198
199 M:: x86 %integer>bignum ( dst src temp -- )
200     #! on entry, inreg is a signed 32-bit quantity
201     #! exits with tagged ptr to bignum in outreg
202     #! 1 cell header, 1 cell length, 1 cell sign, + digits
203     #! length is the # of digits + sign
204     [
205         "end" define-label
206         ! Load cached zero value
207         dst 0 >bignum %load-reference
208         src 0 CMP
209         ! Is it zero? Then just go to the end and return this zero
210         "end" get JE
211         ! Allocate a bignum
212         dst 4 cells bignum temp %allot
213         ! Write length
214         dst 1 bignum@ 2 tag-fixnum MOV
215         ! Store value
216         dst 3 bignum@ src MOV
217         ! Compute sign
218         temp src MOV
219         temp cell-bits 1- SAR
220         temp 1 AND
221         ! Store sign
222         dst 2 bignum@ temp MOV
223         ! Make negative value positive
224         temp temp ADD
225         temp NEG
226         temp 1 ADD
227         src temp IMUL2
228         ! Store the bignum
229         dst 3 bignum@ temp MOV
230         "end" resolve-label
231     ] with-scope ;
232
233 M:: x86 %bignum>integer ( dst src temp -- )
234     [
235         "end" define-label
236         ! load length
237         temp src 1 bignum@ MOV
238         ! if the length is 1, its just the sign and nothing else,
239         ! so output 0
240         dst 0 MOV
241         temp 1 tag-fixnum CMP
242         "end" get JE
243         ! load the value
244         dst src 3 bignum@ MOV
245         ! load the sign
246         temp src 2 bignum@ MOV
247         ! convert it into -1 or 1
248         temp temp ADD
249         temp NEG
250         temp 1 ADD
251         ! make dst signed
252         temp dst IMUL2
253         "end" resolve-label
254     ] with-scope ;
255
256 M: x86 %add-float nip ADDSD ;
257 M: x86 %sub-float nip SUBSD ;
258 M: x86 %mul-float nip MULSD ;
259 M: x86 %div-float nip DIVSD ;
260
261 M: x86 %integer>float CVTSI2SD ;
262 M: x86 %float>integer CVTTSD2SI ;
263
264 M: x86 %copy ( dst src -- ) ?MOV ;
265
266 M: x86 %copy-float ( dst src -- )
267     2dup = [ 2drop ] [ MOVSD ] if ;
268
269 M: x86 %unbox-float ( dst src -- )
270     float-offset [+] MOVSD ;
271
272 M:: x86 %unbox-any-c-ptr ( dst src temp -- )
273     [
274         { "is-byte-array" "end" "start" } [ define-label ] each
275         dst 0 MOV
276         temp src MOV
277         ! We come back here with displaced aliens
278         "start" resolve-label
279         ! Is the object f?
280         temp \ f tag-number CMP
281         "end" get JE
282         ! Is the object an alien?
283         temp header-offset [+] alien type-number tag-fixnum CMP
284         "is-byte-array" get JNE
285         ! If so, load the offset and add it to the address
286         dst temp alien-offset [+] ADD
287         ! Now recurse on the underlying alien
288         temp temp underlying-alien-offset [+] MOV
289         "start" get JMP
290         "is-byte-array" resolve-label
291         ! Add byte array address to address being computed
292         dst temp ADD
293         ! Add an offset to start of byte array's data
294         dst byte-array-offset ADD
295         "end" resolve-label
296     ] with-scope ;
297
298 M:: x86 %box-float ( dst src temp -- )
299     dst 16 float temp %allot
300     dst float-offset [+] src MOVSD ;
301
302 : alien@ ( reg n -- op ) cells alien tag-number - [+] ;
303
304 M:: x86 %box-alien ( dst src temp -- )
305     [
306         "end" define-label
307         dst \ f tag-number MOV
308         src 0 CMP
309         "end" get JE
310         dst 4 cells alien temp %allot
311         dst 1 alien@ \ f tag-number MOV
312         dst 2 alien@ \ f tag-number MOV
313         ! Store src in alien-offset slot
314         dst 3 alien@ src MOV
315         "end" resolve-label
316     ] with-scope ;
317
318 : small-reg-4 ( reg -- reg' )
319     H{
320         { EAX EAX }
321         { ECX ECX }
322         { EDX EDX }
323         { EBX EBX }
324         { ESP ESP }
325         { EBP EBP }
326         { ESI ESP }
327         { EDI EDI }
328
329         { RAX EAX }
330         { RCX ECX }
331         { RDX EDX }
332         { RBX EBX }
333         { RSP ESP }
334         { RBP EBP }
335         { RSI ESP }
336         { RDI EDI }
337     } at ; inline
338
339 : small-reg-2 ( reg -- reg' )
340     small-reg-4 H{
341         { EAX AX }
342         { ECX CX }
343         { EDX DX }
344         { EBX BX }
345         { ESP SP }
346         { EBP BP }
347         { ESI SI }
348         { EDI DI }
349     } at ; inline
350
351 : small-reg-1 ( reg -- reg' )
352     small-reg-4 {
353         { EAX AL }
354         { ECX CL }
355         { EDX DL }
356         { EBX BL }
357     } at ; inline
358
359 : small-reg ( reg size -- reg' )
360     {
361         { 1 [ small-reg-1 ] }
362         { 2 [ small-reg-2 ] }
363         { 4 [ small-reg-4 ] }
364     } case ;
365
366 : small-regs ( -- regs ) { EAX ECX EDX EBX } ; inline
367
368 : small-reg-that-isn't ( exclude -- reg' )
369     small-regs swap [ small-reg-4 ] map '[ _ memq? not ] find nip ;
370
371 : with-save/restore ( reg quot -- )
372     [ drop PUSH ] [ call ] [ drop POP ] 2tri ; inline
373
374 :: with-small-register ( dst exclude quot: ( new-dst -- ) -- )
375     #! If the destination register overlaps a small register, we
376     #! call the quot with that. Otherwise, we find a small
377     #! register that is not in exclude, and call quot, saving
378     #! and restoring the small register.
379     dst small-reg-4 small-regs memq? [ dst quot call ] [
380         exclude small-reg-that-isn't
381         [ quot call ] with-save/restore
382     ] if ; inline
383
384 M:: x86 %string-nth ( dst src index temp -- )
385     "end" define-label
386     dst { src index temp } [| new-dst |
387         ! Load the least significant 7 bits into new-dst.
388         ! 8th bit indicates whether we have to load from
389         ! the aux vector or not.
390         temp src index [+] LEA
391         new-dst 1 small-reg temp string-offset [+] MOV
392         new-dst new-dst 1 small-reg MOVZX
393         ! Do we have to look at the aux vector?
394         new-dst HEX: 80 CMP
395         "end" get JL
396         ! Yes, this is a non-ASCII character. Load aux vector
397         temp src string-aux-offset [+] MOV
398         new-dst temp XCHG
399         ! Compute index
400         new-dst index ADD
401         new-dst index ADD
402         ! Load high 16 bits
403         new-dst 2 small-reg new-dst byte-array-offset [+] MOV
404         new-dst new-dst 2 small-reg MOVZX
405         new-dst 7 SHL
406         ! Compute code point
407         new-dst temp XOR
408         "end" resolve-label
409         dst new-dst ?MOV
410     ] with-small-register ;
411
412 M:: x86 %set-string-nth-fast ( ch str index temp -- )
413     ch { index str temp } [| new-ch |
414         new-ch ch ?MOV
415         temp str index [+] LEA
416         temp string-offset [+] new-ch 1 small-reg MOV
417     ] with-small-register ;
418
419 :: %alien-integer-getter ( dst src size quot -- )
420     dst { src } [| new-dst |
421         new-dst dup size small-reg dup src [] MOV
422         quot call
423         dst new-dst ?MOV
424     ] with-small-register ; inline
425
426 : %alien-unsigned-getter ( dst src size -- )
427     [ MOVZX ] %alien-integer-getter ; inline
428
429 M: x86 %alien-unsigned-1 1 %alien-unsigned-getter ;
430 M: x86 %alien-unsigned-2 2 %alien-unsigned-getter ;
431
432 : %alien-signed-getter ( dst src size -- )
433     [ MOVSX ] %alien-integer-getter ; inline
434
435 M: x86 %alien-signed-1 1 %alien-signed-getter ;
436 M: x86 %alien-signed-2 2 %alien-signed-getter ;
437 M: x86 %alien-signed-4 4 %alien-signed-getter ;
438
439 M: x86 %alien-unsigned-4 4 [ 2drop ] %alien-integer-getter ;
440
441 M: x86 %alien-cell [] MOV ;
442 M: x86 %alien-float dupd [] MOVSS dup CVTSS2SD ;
443 M: x86 %alien-double [] MOVSD ;
444
445 :: %alien-integer-setter ( ptr value size -- )
446     value { ptr } [| new-value |
447         new-value value ?MOV
448         ptr [] new-value size small-reg MOV
449     ] with-small-register ; inline
450
451 M: x86 %set-alien-integer-1 1 %alien-integer-setter ;
452 M: x86 %set-alien-integer-2 2 %alien-integer-setter ;
453 M: x86 %set-alien-integer-4 4 %alien-integer-setter ;
454 M: x86 %set-alien-cell [ [] ] dip MOV ;
455 M: x86 %set-alien-float dup dup CVTSD2SS [ [] ] dip MOVSS ;
456 M: x86 %set-alien-double [ [] ] dip MOVSD ;
457
458 : load-zone-ptr ( reg -- )
459     #! Load pointer to start of zone array
460     0 MOV "nursery" f rc-absolute-cell rel-dlsym ;
461
462 : load-allot-ptr ( nursery-ptr allot-ptr -- )
463     [ drop load-zone-ptr ] [ swap cell [+] MOV ] 2bi ;
464
465 : inc-allot-ptr ( nursery-ptr n -- )
466     [ cell [+] ] dip 8 align ADD ;
467
468 : store-header ( temp class -- )
469     [ [] ] [ type-number tag-fixnum ] bi* MOV ;
470
471 : store-tagged ( dst tag -- )
472     tag-number OR ;
473
474 M:: x86 %allot ( dst size class nursery-ptr -- )
475     nursery-ptr dst load-allot-ptr
476     dst class store-header
477     dst class store-tagged
478     nursery-ptr size inc-allot-ptr ;
479
480 M:: x86 %write-barrier ( src card# table -- )
481     #! Mark the card pointed to by vreg.
482     ! Mark the card
483     card# src MOV
484     card# card-bits SHR
485     table "cards_offset" f %alien-global
486     table table [] MOV
487     table card# [+] card-mark <byte> MOV
488
489     ! Mark the card deck
490     card# deck-bits card-bits - SHR
491     table "decks_offset" f %alien-global
492     table table [] MOV
493     table card# [+] card-mark <byte> MOV ;
494
495 M: x86 %gc ( -- )
496     "end" define-label
497     temp-reg-1 load-zone-ptr
498     temp-reg-2 temp-reg-1 cell [+] MOV
499     temp-reg-2 1024 ADD
500     temp-reg-1 temp-reg-1 3 cells [+] MOV
501     temp-reg-2 temp-reg-1 CMP
502     "end" get JLE
503     %prepare-alien-invoke
504     "minor_gc" f %alien-invoke
505     "end" resolve-label ;
506
507 M: x86 %alien-global
508     [ 0 MOV ] 2dip rc-absolute-cell rel-dlsym ;
509
510 HOOK: stack-reg cpu ( -- reg )
511
512 : decr-stack-reg ( n -- )
513     dup 0 = [ drop ] [ stack-reg swap SUB ] if ;
514
515 : incr-stack-reg ( n -- )
516     dup 0 = [ drop ] [ stack-reg swap ADD ] if ;
517
518 M: x86 %epilogue ( n -- ) cell - incr-stack-reg ;
519
520 :: %boolean ( dst temp word -- )
521     dst \ f tag-number MOV
522     temp 0 MOV \ t rc-absolute-cell rel-immediate
523     dst temp word execute ; inline
524
525 M: x86 %compare ( dst temp cc src1 src2 -- )
526     CMP {
527         { cc< [ \ CMOVL %boolean ] }
528         { cc<= [ \ CMOVLE %boolean ] }
529         { cc> [ \ CMOVG %boolean ] }
530         { cc>= [ \ CMOVGE %boolean ] }
531         { cc= [ \ CMOVE %boolean ] }
532         { cc/= [ \ CMOVNE %boolean ] }
533     } case ;
534
535 M: x86 %compare-imm ( dst temp cc src1 src2 -- )
536     %compare ;
537
538 M: x86 %compare-float ( dst temp cc src1 src2 -- )
539     UCOMISD {
540         { cc< [ \ CMOVB %boolean ] }
541         { cc<= [ \ CMOVBE %boolean ] }
542         { cc> [ \ CMOVA %boolean ] }
543         { cc>= [ \ CMOVAE %boolean ] }
544         { cc= [ \ CMOVE %boolean ] }
545         { cc/= [ \ CMOVNE %boolean ] }
546     } case ;
547
548 M: x86 %compare-branch ( label cc src1 src2 -- )
549     CMP {
550         { cc< [ JL ] }
551         { cc<= [ JLE ] }
552         { cc> [ JG ] }
553         { cc>= [ JGE ] }
554         { cc= [ JE ] }
555         { cc/= [ JNE ] }
556     } case ;
557
558 M: x86 %compare-imm-branch ( label src1 src2 cc -- )
559     %compare-branch ;
560
561 M: x86 %compare-float-branch ( label cc src1 src2 -- )
562     UCOMISD {
563         { cc< [ JB ] }
564         { cc<= [ JBE ] }
565         { cc> [ JA ] }
566         { cc>= [ JAE ] }
567         { cc= [ JE ] }
568         { cc/= [ JNE ] }
569     } case ;
570
571 : stack@ ( n -- op ) stack-reg swap [+] ;
572
573 : param@ ( n -- op ) reserved-area-size + stack@ ;
574
575 : spill-integer-base ( stack-frame -- n )
576     [ params>> ] [ return>> ] bi + reserved-area-size + ;
577
578 : spill-integer@ ( n -- op )
579     cells
580     stack-frame get spill-integer-base
581     + stack@ ;
582
583 : spill-float-base ( stack-frame -- n )
584     [ spill-integer-base ]
585     [ spill-counts>> int-regs swap at int-regs reg-size * ]
586     bi + ;
587
588 : spill-float@ ( n -- op )
589     double-float-regs reg-size *
590     stack-frame get spill-float-base
591     + stack@ ;
592
593 M: x86 %spill-integer ( src n -- ) spill-integer@ swap MOV ;
594 M: x86 %reload-integer ( dst n -- ) spill-integer@ MOV ;
595
596 M: x86 %spill-float ( src n -- ) spill-float@ swap MOVSD ;
597 M: x86 %reload-float ( dst n -- ) spill-float@ MOVSD ;
598
599 M: x86 %loop-entry 16 code-alignment [ NOP ] times ;
600
601 M: int-regs %save-param-reg drop [ param@ ] dip MOV ;
602 M: int-regs %load-param-reg drop swap param@ MOV ;
603
604 GENERIC: MOVSS/D ( dst src reg-class -- )
605
606 M: single-float-regs MOVSS/D drop MOVSS ;
607 M: double-float-regs MOVSS/D drop MOVSD ;
608
609 M: float-regs %save-param-reg [ param@ ] 2dip MOVSS/D ;
610 M: float-regs %load-param-reg [ swap param@ ] dip MOVSS/D ;
611
612 GENERIC: push-return-reg ( reg-class -- )
613 GENERIC: load-return-reg ( n reg-class -- )
614 GENERIC: store-return-reg ( n reg-class -- )
615
616 M: x86 %prepare-alien-invoke
617     #! Save Factor stack pointers in case the C code calls a
618     #! callback which does a GC, which must reliably trace
619     #! all roots.
620     temp-reg-1 "stack_chain" f %alien-global
621     temp-reg-1 temp-reg-1 [] MOV
622     temp-reg-1 [] stack-reg MOV
623     temp-reg-1 [] cell SUB
624     temp-reg-1 2 cells [+] ds-reg MOV
625     temp-reg-1 3 cells [+] rs-reg MOV ;
626
627 M: x86 value-struct? drop t ;
628
629 M: x86 small-enough? ( n -- ? )
630     HEX: -80000000 HEX: 7fffffff between? ;
631
632 : next-stack@ ( n -- operand )
633     #! nth parameter from the next stack frame. Used to box
634     #! input values to callbacks; the callback has its own
635     #! stack frame set up, and we want to read the frame
636     #! set up by the caller.
637     stack-frame get total-size>> + stack@ ;