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