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