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