]> gitweb.factorcode.org Git - factor.git/blob - basis/cpu/x86/x86.factor
Fix conflicts
[factor.git] / basis / cpu / x86 / x86.factor
1 ! Copyright (C) 2005, 2009 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.x86.assembler.operands
5 cpu.architecture kernel kernel.private math memory namespaces make
6 sequences words system layouts combinators math.order fry locals
7 compiler.constants byte-arrays
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@ ( n -- op ) spill-offset param@ ;
34
35 : gc-root@ ( n -- op ) gc-root-offset param@ ;
36
37 : decr-stack-reg ( n -- )
38     dup 0 = [ drop ] [ stack-reg swap SUB ] if ;
39
40 : incr-stack-reg ( n -- )
41     dup 0 = [ drop ] [ stack-reg swap ADD ] if ;
42
43 : align-stack ( n -- n' )
44     os macosx? cpu x86.64? or [ 16 align ] when ;
45
46 M: x86 stack-frame-size ( stack-frame -- i )
47     (stack-frame-size) 3 cells reserved-area-size + + align-stack ;
48
49 ! Must be a volatile register not used for parameter passing, for safe
50 ! use in calls in and out of C
51 HOOK: temp-reg cpu ( -- reg )
52
53 ! Fastcall calling convention
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 dup 0 = [ drop dup XOR ] [ MOV ] if ;
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     2over eq? [ nip ADD ] [ [+] LEA ] if ;
112 M: x86 %add-imm 2over eq? [ nip ADD ] [ [+] LEA ] if ;
113 M: x86 %sub     nip SUB ;
114 M: x86 %sub-imm 2over eq? [ nip SUB ] [ neg [+] LEA ] if ;
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
127 M: x86 %min     nip [ CMP ] [ CMOVG ] 2bi ;
128 M: x86 %max     nip [ CMP ] [ CMOVL ] 2bi ;
129
130 M: x86 %not     drop NOT ;
131 M: x86 %log2    BSR ;
132
133 GENERIC: copy-register* ( dst src rep -- )
134
135 M: int-rep copy-register* drop MOV ;
136 M: tagged-rep copy-register* drop MOV ;
137 M: float-rep copy-register* drop MOVSS ;
138 M: double-rep copy-register* drop MOVSD ;
139 M: float-4-rep copy-register* drop MOVUPS ;
140 M: double-2-rep copy-register* drop MOVUPD ;
141 M: vector-rep copy-register* drop MOVDQU ;
142
143 : copy-register ( dst src rep -- )
144     2over eq? [ 3drop ] [ copy-register* ] if ;
145
146 M: x86 %copy ( dst src rep -- ) copy-register ;
147
148 :: overflow-template ( label dst src1 src2 insn -- )
149     src1 src2 insn call
150     label JO ; inline
151
152 M: x86 %fixnum-add ( label dst src1 src2 -- )
153     [ ADD ] overflow-template ;
154
155 M: x86 %fixnum-sub ( label dst src1 src2 -- )
156     [ SUB ] overflow-template ;
157
158 M: x86 %fixnum-mul ( label dst src1 src2 -- )
159     [ swap IMUL2 ] overflow-template ;
160
161 : bignum@ ( reg n -- op )
162     cells bignum tag-number - [+] ; inline
163
164 M:: x86 %integer>bignum ( dst src temp -- )
165     #! on entry, inreg is a signed 32-bit quantity
166     #! exits with tagged ptr to bignum in outreg
167     #! 1 cell header, 1 cell length, 1 cell sign, + digits
168     #! length is the # of digits + sign
169     [
170         "end" define-label
171         ! Load cached zero value
172         dst 0 >bignum %load-reference
173         src 0 CMP
174         ! Is it zero? Then just go to the end and return this zero
175         "end" get JE
176         ! Allocate a bignum
177         dst 4 cells bignum temp %allot
178         ! Write length
179         dst 1 bignum@ 2 tag-fixnum MOV
180         ! Store value
181         dst 3 bignum@ src MOV
182         ! Compute sign
183         temp src MOV
184         temp cell-bits 1 - SAR
185         temp 1 AND
186         ! Store sign
187         dst 2 bignum@ temp MOV
188         ! Make negative value positive
189         temp temp ADD
190         temp NEG
191         temp 1 ADD
192         src temp IMUL2
193         ! Store the bignum
194         dst 3 bignum@ temp MOV
195         "end" resolve-label
196     ] with-scope ;
197
198 M:: x86 %bignum>integer ( dst src temp -- )
199     [
200         "end" define-label
201         ! load length
202         temp src 1 bignum@ MOV
203         ! if the length is 1, its just the sign and nothing else,
204         ! so output 0
205         dst 0 MOV
206         temp 1 tag-fixnum CMP
207         "end" get JE
208         ! load the value
209         dst src 3 bignum@ MOV
210         ! load the sign
211         temp src 2 bignum@ MOV
212         ! convert it into -1 or 1
213         temp temp ADD
214         temp NEG
215         temp 1 ADD
216         ! make dst signed
217         temp dst IMUL2
218         "end" resolve-label
219     ] with-scope ;
220
221 M: x86 %add-float nip ADDSD ;
222 M: x86 %sub-float nip SUBSD ;
223 M: x86 %mul-float nip MULSD ;
224 M: x86 %div-float nip DIVSD ;
225 M: x86 %min-float nip MINSD ;
226 M: x86 %max-float nip MAXSD ;
227 M: x86 %sqrt SQRTSD ;
228
229 M: x86 %single>double-float CVTSS2SD ;
230 M: x86 %double>single-float CVTSD2SS ;
231
232 M: x86 %integer>float CVTSI2SD ;
233 M: x86 %float>integer CVTTSD2SI ;
234
235 M: x86 %unbox-float ( dst src -- )
236     float-offset [+] MOVSD ;
237
238 M:: x86 %box-float ( dst src temp -- )
239     dst 16 float temp %allot
240     dst float-offset [+] src MOVSD ;
241
242 M:: x86 %box-vector ( dst src rep temp -- )
243     dst rep rep-size 2 cells + byte-array temp %allot
244     16 tag-fixnum dst 1 byte-array tag-number %set-slot-imm
245     dst byte-array-offset [+]
246     src rep copy-register ;
247
248 M:: x86 %unbox-vector ( dst src rep -- )
249     dst src byte-array-offset [+]
250     rep copy-register ;
251
252 M: x86 %broadcast-vector ( dst src rep -- )
253     {
254         { float-4-rep [ [ MOVAPS ] [ drop dup 0 SHUFPS ] 2bi ] }
255         { double-2-rep [ [ MOVAPD ] [ drop dup 0 SHUFPD ] 2bi ] }
256     } case ;
257
258 M:: x86 %gather-vector-4 ( dst src1 src2 src3 src4 rep -- )
259     rep {
260         {
261             float-4-rep
262             [
263                 dst src1 MOVSS
264                 dst src2 UNPCKLPS
265                 src3 src4 UNPCKLPS
266                 dst src3 HEX: 44 SHUFPS
267             ]
268         }
269     } case ;
270
271 M:: x86 %gather-vector-2 ( dst src1 src2 rep -- )
272     rep {
273         {
274             double-2-rep
275             [
276                 dst src1 MOVAPD
277                 dst src2 0 SHUFPD
278             ]
279         }
280     } case ;
281
282 M: x86 %add-vector ( dst src1 src2 rep -- )
283     {
284         { float-4-rep [ ADDPS ] }
285         { double-2-rep [ ADDPD ] }
286         { char-16-rep [ PADDB ] }
287         { uchar-16-rep [ PADDB ] }
288         { short-8-rep [ PADDW ] }
289         { ushort-8-rep [ PADDW ] }
290         { int-4-rep [ PADDD ] }
291         { uint-4-rep [ PADDD ] }
292     } case drop ;
293
294 M: x86 %sub-vector ( dst src1 src2 rep -- )
295     {
296         { float-4-rep [ SUBPS ] }
297         { double-2-rep [ SUBPD ] }
298         { char-16-rep [ PSUBB ] }
299         { uchar-16-rep [ PSUBB ] }
300         { short-8-rep [ PSUBW ] }
301         { ushort-8-rep [ PSUBW ] }
302         { int-4-rep [ PSUBD ] }
303         { uint-4-rep [ PSUBD ] }
304     } case drop ;
305
306 M: x86 %mul-vector ( dst src1 src2 rep -- )
307     {
308         { float-4-rep [ MULPS ] }
309         { double-2-rep [ MULPD ] }
310         { int-4-rep [ PMULLW ] }
311     } case drop ;
312
313 M: x86 %div-vector ( dst src1 src2 rep -- )
314     {
315         { float-4-rep [ DIVPS ] }
316         { double-2-rep [ DIVPD ] }
317     } case drop ;
318
319 M: x86 %min-vector ( dst src1 src2 rep -- )
320     {
321         { float-4-rep [ MINPS ] }
322         { double-2-rep [ MINPD ] }
323     } case drop ;
324
325 M: x86 %max-vector ( dst src1 src2 rep -- )
326     {
327         { float-4-rep [ MAXPS ] }
328         { double-2-rep [ MAXPD ] }
329     } case drop ;
330
331 M: x86 %sqrt-vector ( dst src rep -- )
332     {
333         { float-4-rep [ SQRTPS ] }
334         { double-2-rep [ SQRTPD ] }
335     } case ;
336
337 M: x86 %horizontal-add-vector ( dst src rep -- )
338     {
339         { float-4-rep [ [ MOVAPS ] [ HADDPS ] [ HADDPS ] 2tri ] }
340         { double-2-rep [ [ MOVAPD ] [ HADDPD ] 2bi ] }
341     } case ;
342
343 M: x86 %unbox-alien ( dst src -- )
344     alien-offset [+] MOV ;
345
346 M:: x86 %unbox-any-c-ptr ( dst src temp -- )
347     [
348         { "is-byte-array" "end" "start" } [ define-label ] each
349         dst 0 MOV
350         temp src MOV
351         ! We come back here with displaced aliens
352         "start" resolve-label
353         ! Is the object f?
354         temp \ f tag-number CMP
355         "end" get JE
356         ! Is the object an alien?
357         temp header-offset [+] alien type-number tag-fixnum CMP
358         "is-byte-array" get JNE
359         ! If so, load the offset and add it to the address
360         dst temp alien-offset [+] ADD
361         ! Now recurse on the underlying alien
362         temp temp underlying-alien-offset [+] MOV
363         "start" get JMP
364         "is-byte-array" resolve-label
365         ! Add byte array address to address being computed
366         dst temp ADD
367         ! Add an offset to start of byte array's data
368         dst byte-array-offset ADD
369         "end" resolve-label
370     ] with-scope ;
371
372 : alien@ ( reg n -- op ) cells alien tag-number - [+] ;
373
374 :: %allot-alien ( dst displacement base temp -- )
375     dst 4 cells alien temp %allot
376     dst 1 alien@ base MOV ! alien
377     dst 2 alien@ \ f tag-number MOV ! expired
378     dst 3 alien@ displacement MOV ! displacement
379     ;
380
381 M:: x86 %box-alien ( dst src temp -- )
382     [
383         "end" define-label
384         dst \ f tag-number MOV
385         src 0 CMP
386         "end" get JE
387         dst src \ f tag-number temp %allot-alien
388         "end" resolve-label
389     ] with-scope ;
390
391 M:: x86 %box-displaced-alien ( dst displacement base displacement' base' base-class -- )
392     [
393         "end" define-label
394         "ok" define-label
395         ! If displacement is zero, return the base
396         dst base MOV
397         displacement 0 CMP
398         "end" get JE
399         ! Quickly use displacement' before its needed for real, as allot temporary
400         dst 4 cells alien displacement' %allot
401         ! If base is already a displaced alien, unpack it
402         base' base MOV
403         displacement' displacement MOV
404         base \ f tag-number CMP
405         "ok" get JE
406         base header-offset [+] alien type-number tag-fixnum CMP
407         "ok" get JNE
408         ! displacement += base.displacement
409         displacement' base 3 alien@ ADD
410         ! base = base.base
411         base' base 1 alien@ MOV
412         "ok" resolve-label
413         dst 1 alien@ base' MOV ! alien
414         dst 2 alien@ \ f tag-number MOV ! expired
415         dst 3 alien@ displacement' MOV ! displacement
416         "end" resolve-label
417     ] with-scope ;
418
419 ! The 'small-reg' mess is pretty crappy, but its only used on x86-32.
420 ! On x86-64, all registers have 8-bit versions. However, a similar
421 ! problem arises for shifts, where the shift count must be in CL, and
422 ! so one day I will fix this properly by adding precoloring to the
423 ! register allocator.
424
425 HOOK: has-small-reg? cpu ( reg size -- ? )
426
427 CONSTANT: have-byte-regs { EAX ECX EDX EBX }
428
429 M: x86.32 has-small-reg?
430     {
431         { 8 [ have-byte-regs memq? ] }
432         { 16 [ drop t ] }
433         { 32 [ drop t ] }
434     } case ;
435
436 M: x86.64 has-small-reg? 2drop t ;
437
438 : small-reg-that-isn't ( exclude -- reg' )
439     [ have-byte-regs ] dip
440     [ native-version-of ] map
441     '[ _ memq? not ] find nip ;
442
443 : with-save/restore ( reg quot -- )
444     [ drop PUSH ] [ call ] [ drop POP ] 2tri ; inline
445
446 :: with-small-register ( dst exclude size quot: ( new-dst -- ) -- )
447     ! If the destination register overlaps a small register with
448     ! 'size' bits, we call the quot with that. Otherwise, we find a
449     ! small register that is not in exclude, and call quot, saving and
450     ! restoring the small register.
451     dst size has-small-reg? [ dst quot call ] [
452         exclude small-reg-that-isn't
453         [ quot call ] with-save/restore
454     ] if ; inline
455
456 : ?MOV ( dst src -- )
457     2dup = [ 2drop ] [ MOV ] if ; inline
458
459 M:: x86 %string-nth ( dst src index temp -- )
460     ! We request a small-reg of size 8 since those of size 16 are
461     ! a superset.
462     "end" define-label
463     dst { src index temp } 8 [| new-dst |
464         ! Load the least significant 7 bits into new-dst.
465         ! 8th bit indicates whether we have to load from
466         ! the aux vector or not.
467         temp src index [+] LEA
468         new-dst 8-bit-version-of temp string-offset [+] MOV
469         new-dst new-dst 8-bit-version-of MOVZX
470         ! Do we have to look at the aux vector?
471         new-dst HEX: 80 CMP
472         "end" get JL
473         ! Yes, this is a non-ASCII character. Load aux vector
474         temp src string-aux-offset [+] MOV
475         new-dst temp XCHG
476         ! Compute index
477         new-dst index ADD
478         new-dst index ADD
479         ! Load high 16 bits
480         new-dst 16-bit-version-of new-dst byte-array-offset [+] MOV
481         new-dst new-dst 16-bit-version-of MOVZX
482         new-dst 7 SHL
483         ! Compute code point
484         new-dst temp XOR
485         "end" resolve-label
486         dst new-dst ?MOV
487     ] with-small-register ;
488
489 M:: x86 %set-string-nth-fast ( ch str index temp -- )
490     ch { index str temp } 8 [| new-ch |
491         new-ch ch ?MOV
492         temp str index [+] LEA
493         temp string-offset [+] new-ch 8-bit-version-of MOV
494     ] with-small-register ;
495
496 :: %alien-integer-getter ( dst src size quot -- )
497     dst { src } size [| new-dst |
498         new-dst dup size n-bit-version-of dup src [] MOV
499         quot call
500         dst new-dst ?MOV
501     ] with-small-register ; inline
502
503 : %alien-unsigned-getter ( dst src size -- )
504     [ MOVZX ] %alien-integer-getter ; inline
505
506 M: x86 %alien-unsigned-1 8 %alien-unsigned-getter ;
507 M: x86 %alien-unsigned-2 16 %alien-unsigned-getter ;
508 M: x86 %alien-unsigned-4 32 [ 2drop ] %alien-integer-getter ;
509
510 : %alien-signed-getter ( dst src size -- )
511     [ MOVSX ] %alien-integer-getter ; inline
512
513 M: x86 %alien-signed-1 8 %alien-signed-getter ;
514 M: x86 %alien-signed-2 16 %alien-signed-getter ;
515 M: x86 %alien-signed-4 32 %alien-signed-getter ;
516
517 M: x86 %alien-cell [] MOV ;
518 M: x86 %alien-float [] MOVSS ;
519 M: x86 %alien-double [] MOVSD ;
520 M: x86 %alien-vector [ [] ] dip copy-register ;
521
522 :: %alien-integer-setter ( ptr value size -- )
523     value { ptr } size [| new-value |
524         new-value value ?MOV
525         ptr [] new-value size n-bit-version-of MOV
526     ] with-small-register ; inline
527
528 M: x86 %set-alien-integer-1 8 %alien-integer-setter ;
529 M: x86 %set-alien-integer-2 16 %alien-integer-setter ;
530 M: x86 %set-alien-integer-4 32 %alien-integer-setter ;
531 M: x86 %set-alien-cell [ [] ] dip MOV ;
532 M: x86 %set-alien-float [ [] ] dip MOVSS ;
533 M: x86 %set-alien-double [ [] ] dip MOVSD ;
534 M: x86 %set-alien-vector [ [] ] 2dip copy-register ;
535
536 : shift-count? ( reg -- ? ) { ECX RCX } memq? ;
537
538 :: emit-shift ( dst src1 src2 quot -- )
539     src2 shift-count? [
540         dst CL quot call
541     ] [
542         dst shift-count? [
543             dst src2 XCHG
544             src2 CL quot call
545             dst src2 XCHG
546         ] [
547             ECX native-version-of [
548                 CL src2 MOV
549                 drop dst CL quot call
550             ] with-save/restore
551         ] if
552     ] if ; inline
553
554 M: x86 %shl [ SHL ] emit-shift ;
555 M: x86 %shr [ SHR ] emit-shift ;
556 M: x86 %sar [ SAR ] emit-shift ;
557
558 : load-zone-ptr ( reg -- )
559     #! Load pointer to start of zone array
560     0 MOV "nursery" f rc-absolute-cell rel-dlsym ;
561
562 : load-allot-ptr ( nursery-ptr allot-ptr -- )
563     [ drop load-zone-ptr ] [ swap cell [+] MOV ] 2bi ;
564
565 : inc-allot-ptr ( nursery-ptr n -- )
566     [ cell [+] ] dip 8 align ADD ;
567
568 : store-header ( temp class -- )
569     [ [] ] [ type-number tag-fixnum ] bi* MOV ;
570
571 : store-tagged ( dst tag -- )
572     tag-number OR ;
573
574 M:: x86 %allot ( dst size class nursery-ptr -- )
575     nursery-ptr dst load-allot-ptr
576     dst class store-header
577     dst class store-tagged
578     nursery-ptr size inc-allot-ptr ;
579
580 M:: x86 %write-barrier ( src card# table -- )
581     #! Mark the card pointed to by vreg.
582     ! Mark the card
583     card# src MOV
584     card# card-bits SHR
585     table "cards_offset" f %alien-global
586     table table [] MOV
587     table card# [+] card-mark <byte> MOV
588
589     ! Mark the card deck
590     card# deck-bits card-bits - SHR
591     table "decks_offset" f %alien-global
592     table table [] MOV
593     table card# [+] card-mark <byte> MOV ;
594
595 M:: x86 %check-nursery ( label temp1 temp2 -- )
596     temp1 load-zone-ptr
597     temp2 temp1 cell [+] MOV
598     temp2 1024 ADD
599     temp1 temp1 3 cells [+] MOV
600     temp2 temp1 CMP
601     label JLE ;
602
603 M: x86 %save-gc-root ( gc-root register -- ) [ gc-root@ ] dip MOV ;
604
605 M: x86 %load-gc-root ( gc-root register -- ) swap gc-root@ MOV ;
606
607 M:: x86 %call-gc ( gc-root-count -- )
608     ! Pass pointer to start of GC roots as first parameter
609     param-reg-1 gc-root-base param@ LEA
610     ! Pass number of roots as second parameter
611     param-reg-2 gc-root-count MOV
612     ! Call GC
613     %prepare-alien-invoke
614     "inline_gc" f %alien-invoke ;
615
616 M: x86 %alien-global
617     [ 0 MOV ] 2dip rc-absolute-cell rel-dlsym ;
618
619 M: x86 %epilogue ( n -- ) cell - incr-stack-reg ;
620
621 :: %boolean ( dst temp word -- )
622     dst \ f tag-number MOV
623     temp 0 MOV \ t rc-absolute-cell rel-immediate
624     dst temp word execute ; inline
625
626 M: x86 %compare ( dst src1 src2 cc temp -- )
627     src1 src2 CMP
628     cc order-cc {
629         { cc<  [ dst temp \ CMOVL %boolean ] }
630         { cc<= [ dst temp \ CMOVLE %boolean ] }
631         { cc>  [ dst temp \ CMOVG %boolean ] }
632         { cc>= [ dst temp \ CMOVGE %boolean ] }
633         { cc=  [ dst temp \ CMOVE %boolean ] }
634         { cc/= [ dst temp \ CMOVNE %boolean ] }
635     } case ;
636
637 M: x86 %compare-imm ( dst src1 src2 cc temp -- )
638     %compare ;
639
640 : %cmov-float= ( dst src -- )
641     [
642         "no-move" define-label
643
644         "no-move" get [ JNE ] [ JP ] bi
645         MOV
646         "no-move" resolve-label
647     ] with-scope ;
648
649 : %cmov-float/= ( dst src -- )
650     [
651         "no-move" define-label
652         "move" define-label
653
654         "move" get JP
655         "no-move" get JE
656         "move" resolve-label
657         MOV
658         "no-move" resolve-label
659     ] with-scope ;
660
661 M:: x86 %compare-float ( dst src1 src2 cc temp -- )
662     cc {
663         { cc<    [ src2 src1  COMISD dst temp \ CMOVA  %boolean ] }
664         { cc<=   [ src2 src1  COMISD dst temp \ CMOVAE %boolean ] }
665         { cc>    [ src1 src2  COMISD dst temp \ CMOVA  %boolean ] }
666         { cc>=   [ src1 src2  COMISD dst temp \ CMOVAE %boolean ] }
667         { cc=    [ src1 src2 UCOMISD dst temp \ %cmov-float= %boolean ] }
668         { cc<>   [ src1 src2  COMISD dst temp \ CMOVNE %boolean ] }
669         { cc<>=  [ src1 src2  COMISD dst temp \ CMOVNP %boolean ] }
670         { cc/<   [ src2 src1 UCOMISD dst temp \ CMOVBE %boolean ] }
671         { cc/<=  [ src2 src1 UCOMISD dst temp \ CMOVB  %boolean ] }
672         { cc/>   [ src1 src2 UCOMISD dst temp \ CMOVBE %boolean ] }
673         { cc/>=  [ src1 src2 UCOMISD dst temp \ CMOVB  %boolean ] }
674         { cc/=   [ src1 src2 UCOMISD dst temp \ %cmov-float/= %boolean ] }
675         { cc/<>  [ src1 src2 UCOMISD dst temp \ CMOVE  %boolean ] }
676         { cc/<>= [ src1 src2 UCOMISD dst temp \ CMOVP  %boolean ] }
677     } case ;
678
679 M:: x86 %compare-branch ( label src1 src2 cc -- )
680     src1 src2 CMP
681     cc order-cc {
682         { cc<  [ label JL ] }
683         { cc<= [ label JLE ] }
684         { cc>  [ label JG ] }
685         { cc>= [ label JGE ] }
686         { cc=  [ label JE ] }
687         { cc/= [ label JNE ] }
688     } case ;
689
690 M: x86 %compare-imm-branch ( label src1 src2 cc -- )
691     %compare-branch ;
692
693 : %jump-float= ( label -- )
694     [
695         "no-jump" define-label
696         "no-jump" get JP
697         JE
698         "no-jump" resolve-label
699     ] with-scope ;
700
701 : %jump-float/= ( label -- )
702     [ JNE ] [ JP ] bi ;
703
704 M:: x86 %compare-float-branch ( label src1 src2 cc -- )
705     cc {
706         { cc<    [ src2 src1  COMISD label JA  ] }
707         { cc<=   [ src2 src1  COMISD label JAE ] }
708         { cc>    [ src1 src2  COMISD label JA  ] }
709         { cc>=   [ src1 src2  COMISD label JAE ] }
710         { cc=    [ src1 src2 UCOMISD label %jump-float= ] }
711         { cc<>   [ src1 src2  COMISD label JNE ] }
712         { cc<>=  [ src1 src2  COMISD label JNP ] }
713         { cc/<   [ src2 src1 UCOMISD label JBE ] }
714         { cc/<=  [ src2 src1 UCOMISD label JB  ] }
715         { cc/>   [ src1 src2 UCOMISD label JBE ] }
716         { cc/>=  [ src1 src2 UCOMISD label JB  ] }
717         { cc/=   [ src1 src2 UCOMISD label %jump-float/= ] }
718         { cc/<>  [ src1 src2 UCOMISD label JE  ] }
719         { cc/<>= [ src1 src2 UCOMISD label JP  ] }
720     } case ;
721
722 M:: x86 %spill ( src rep n -- )
723     n spill@ src rep copy-register ;
724
725 M:: x86 %reload ( dst rep n -- )
726     dst n spill@ rep copy-register ;
727
728 M: x86 %loop-entry 16 code-alignment [ NOP ] times ;
729
730 M: x86 %prepare-alien-invoke
731     #! Save Factor stack pointers in case the C code calls a
732     #! callback which does a GC, which must reliably trace
733     #! all roots.
734     temp-reg "stack_chain" f %alien-global
735     temp-reg temp-reg [] MOV
736     temp-reg [] stack-reg MOV
737     temp-reg [] cell SUB
738     temp-reg 2 cells [+] ds-reg MOV
739     temp-reg 3 cells [+] rs-reg MOV ;
740
741 M: x86 value-struct? drop t ;
742
743 M: x86 small-enough? ( n -- ? )
744     HEX: -80000000 HEX: 7fffffff between? ;
745
746 : next-stack@ ( n -- operand )
747     #! nth parameter from the next stack frame. Used to box
748     #! input values to callbacks; the callback has its own
749     #! stack frame set up, and we want to read the frame
750     #! set up by the caller.
751     stack-frame get total-size>> + stack@ ;
752
753 : enable-sse2 ( -- )
754     enable-float-intrinsics
755     enable-fsqrt
756     enable-float-min/max
757     enable-sse2-simd ;
758
759 : enable-sse3 ( -- )
760     enable-sse2
761     enable-sse3-simd ;
762
763 enable-min/max