]> gitweb.factorcode.org Git - factor.git/blob - basis/cpu/x86/x86.factor
GC maps for more compact inline GC checks
[factor.git] / basis / cpu / x86 / x86.factor
1 ! Copyright (C) 2005, 2010 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.x86.features cpu.x86.features.private cpu.architecture kernel
6 kernel.private math memory namespaces make sequences words system
7 layouts combinators math.order math.vectors fry locals compiler.constants
8 byte-arrays io macros quotations classes.algebra compiler
9 compiler.units init vm vocabs.loader
10 compiler.cfg.registers
11 compiler.cfg.instructions
12 compiler.cfg.intrinsics
13 compiler.cfg.comparisons
14 compiler.cfg.stack-frame
15 compiler.codegen.fixup ;
16 QUALIFIED-WITH: alien.c-types c
17 FROM: layouts => cell ;
18 FROM: math => float ;
19 IN: cpu.x86
20
21 ! Add some methods to the assembler to be more useful to the backend
22 M: label JMP 0 JMP rc-relative label-fixup ;
23 M: label JUMPcc [ 0 ] dip JUMPcc rc-relative label-fixup ;
24
25 M: x86 vector-regs float-regs ;
26
27 HOOK: stack-reg cpu ( -- reg )
28
29 HOOK: reserved-stack-space cpu ( -- n )
30
31 : stack@ ( n -- op ) stack-reg swap [+] ;
32
33 : special-offset ( m -- n )
34     reserved-stack-space + ;
35
36 : spill@ ( n -- op ) spill-offset special-offset stack@ ;
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' ) 16 align ;
45
46 M: x86 stack-frame-size ( stack-frame -- i )
47     (stack-frame-size)
48     reserved-stack-space +
49     3 cells +
50     align-stack ;
51
52 HOOK: pic-tail-reg cpu ( -- reg )
53
54 M: x86 complex-addressing? t ;
55
56 M: x86 fused-unboxing? t ;
57
58 M: x86 test-instruction? t ;
59
60 M: x86 immediate-store? immediate-comparand? ;
61
62 M: x86 %load-immediate dup 0 = [ drop dup XOR ] [ MOV ] if ;
63
64 M: x86 %load-reference
65     [ swap 0 MOV rc-absolute-cell rel-literal ]
66     [ \ f type-number MOV ]
67     if* ;
68
69 HOOK: ds-reg cpu ( -- reg )
70 HOOK: rs-reg cpu ( -- reg )
71
72 : reg-stack ( n reg -- op ) swap cells neg [+] ;
73
74 GENERIC: loc>operand ( loc -- operand )
75
76 M: ds-loc loc>operand n>> ds-reg reg-stack ;
77 M: rs-loc loc>operand n>> rs-reg reg-stack ;
78
79 M: x86 %peek loc>operand MOV ;
80
81 M: x86 %replace loc>operand swap MOV ;
82
83 M: x86 %replace-imm
84     loc>operand swap
85     {
86         { [ dup not ] [ drop \ f type-number MOV ] }
87         { [ dup fixnum? ] [ tag-fixnum MOV ] }
88         [ [ HEX: ffffffff MOV ] dip rc-absolute rel-literal ]
89     } cond ;
90
91 : (%inc) ( n reg -- ) swap cells dup 0 > [ ADD ] [ neg SUB ] if ; inline
92 M: x86 %inc-d ( n -- ) ds-reg (%inc) ;
93 M: x86 %inc-r ( n -- ) rs-reg (%inc) ;
94
95 M: x86 %call ( word -- ) 0 CALL rc-relative rel-word-pic ;
96
97 : xt-tail-pic-offset ( -- n )
98     #! See the comment in vm/cpu-x86.hpp
99     4 1 + ; inline
100
101 HOOK: %prepare-jump cpu ( -- )
102
103 M: x86 %jump ( word -- )
104     %prepare-jump
105     0 JMP rc-relative rel-word-pic-tail ;
106
107 M: x86 %jump-label ( label -- ) 0 JMP rc-relative label-fixup ;
108
109 M: x86 %return ( -- ) 0 RET ;
110
111 : (%slot) ( obj slot scale tag -- op ) neg <indirect> ; inline
112 : (%slot-imm) ( obj slot tag -- op ) slot-offset [+] ; inline
113
114 M: x86 %slot ( dst obj slot scale tag -- ) (%slot) MOV ;
115 M: x86 %slot-imm ( dst obj slot tag -- ) (%slot-imm) MOV ;
116 M: x86 %set-slot ( src obj slot scale tag -- ) (%slot) swap MOV ;
117 M: x86 %set-slot-imm ( src obj slot tag -- ) (%slot-imm) swap MOV ;
118
119 :: two-operand ( dst src1 src2 rep -- dst src )
120     dst src2 eq? dst src1 eq? not and [ "Cannot handle this case" throw ] when
121     dst src1 rep %copy
122     dst src2 ; inline
123
124 :: one-operand ( dst src rep -- dst )
125     dst src rep %copy
126     dst ; inline
127
128 M: x86 %add     2over eq? [ nip ADD ] [ [+] LEA ] if ;
129 M: x86 %add-imm 2over eq? [ nip ADD ] [ [+] LEA ] if ;
130 M: x86 %sub     int-rep two-operand SUB ;
131 M: x86 %sub-imm 2over eq? [ nip SUB ] [ neg [+] LEA ] if ;
132 M: x86 %mul     int-rep two-operand IMUL2 ;
133 M: x86 %mul-imm IMUL3 ;
134 M: x86 %and     int-rep two-operand AND ;
135 M: x86 %and-imm int-rep two-operand AND ;
136 M: x86 %or      int-rep two-operand OR ;
137 M: x86 %or-imm  int-rep two-operand OR ;
138 M: x86 %xor     int-rep two-operand XOR ;
139 M: x86 %xor-imm int-rep two-operand XOR ;
140 M: x86 %shl-imm int-rep two-operand SHL ;
141 M: x86 %shr-imm int-rep two-operand SHR ;
142 M: x86 %sar-imm int-rep two-operand SAR ;
143
144 M: x86 %min     int-rep two-operand [ CMP ] [ CMOVG ] 2bi ;
145 M: x86 %max     int-rep two-operand [ CMP ] [ CMOVL ] 2bi ;
146
147 M: x86 %not     int-rep one-operand NOT ;
148 M: x86 %neg     int-rep one-operand NEG ;
149 M: x86 %log2    BSR ;
150 M: x86 %bit-count POPCNT ;
151
152 ! A bit of logic to avoid using MOVSS/MOVSD for reg-reg moves
153 ! since this induces partial register stalls
154 GENERIC: copy-register* ( dst src rep -- )
155 GENERIC: copy-memory* ( dst src rep -- )
156
157 M: int-rep copy-register* drop MOV ;
158 M: tagged-rep copy-register* drop MOV ;
159
160 M: object copy-memory* copy-register* ;
161
162 : ?spill-slot ( obj -- obj ) dup spill-slot? [ n>> spill@ ] when ;
163
164 M: x86 %copy ( dst src rep -- )
165     2over eq? [ 3drop ] [
166         [ [ ?spill-slot ] bi@ ] dip
167         2over [ register? ] both? [ copy-register* ] [ copy-memory* ] if
168     ] if ;
169
170 : fixnum-overflow ( label dst src1 src2 cc quot -- )
171     swap [ [ int-rep two-operand ] dip call ] dip
172     {
173         { cc-o [ JO ] }
174         { cc/o [ JNO ] }
175     } case ; inline
176
177 M: x86 %fixnum-add ( label dst src1 src2 cc -- )
178     [ ADD ] fixnum-overflow ;
179
180 M: x86 %fixnum-sub ( label dst src1 src2 cc -- )
181     [ SUB ] fixnum-overflow ;
182
183 M: x86 %fixnum-mul ( label dst src1 src2 cc -- )
184     [ IMUL2 ] fixnum-overflow ;
185
186 M: x86 %unbox-alien ( dst src -- )
187     alien-offset [+] MOV ;
188
189 M:: x86 %unbox-any-c-ptr ( dst src -- )
190     [
191         "end" define-label
192         dst dst XOR
193         ! Is the object f?
194         src \ f type-number CMP
195         "end" get JE
196         ! Compute tag in dst register
197         dst src MOV
198         dst tag-mask get AND
199         ! Is the object an alien?
200         dst alien type-number CMP
201         ! Add an offset to start of byte array's data
202         dst src byte-array-offset [+] LEA
203         "end" get JNE
204         ! If so, load the offset and add it to the address
205         dst src alien-offset [+] MOV
206         "end" resolve-label
207     ] with-scope ;
208
209 : alien@ ( reg n -- op ) cells alien type-number - [+] ;
210
211 M:: x86 %box-alien ( dst src temp -- )
212     [
213         "end" define-label
214         dst \ f type-number MOV
215         src src TEST
216         "end" get JE
217         dst 5 cells alien temp %allot
218         dst 1 alien@ \ f type-number MOV ! base
219         dst 2 alien@ \ f type-number MOV ! expired
220         dst 3 alien@ src MOV ! displacement
221         dst 4 alien@ src MOV ! address
222         "end" resolve-label
223     ] with-scope ;
224
225 :: %box-displaced-alien/f ( dst displacement -- )
226     dst 1 alien@ \ f type-number MOV
227     dst 3 alien@ displacement MOV
228     dst 4 alien@ displacement MOV ;
229
230 :: %box-displaced-alien/alien ( dst displacement base temp -- )
231     ! Set new alien's base to base.base
232     temp base 1 alien@ MOV
233     dst 1 alien@ temp MOV
234
235     ! Compute displacement
236     temp base 3 alien@ MOV
237     temp displacement ADD
238     dst 3 alien@ temp MOV
239
240     ! Compute address
241     temp base 4 alien@ MOV
242     temp displacement ADD
243     dst 4 alien@ temp MOV ;
244
245 :: %box-displaced-alien/byte-array ( dst displacement base temp -- )
246     dst 1 alien@ base MOV
247     dst 3 alien@ displacement MOV
248     temp base displacement byte-array-offset [++] LEA
249     dst 4 alien@ temp MOV ;
250
251 :: %box-displaced-alien/dynamic ( dst displacement base temp -- )
252     "not-f" define-label
253     "not-alien" define-label
254
255     ! Check base type
256     temp base MOV
257     temp tag-mask get AND
258
259     ! Is base f?
260     temp \ f type-number CMP
261     "not-f" get JNE
262
263     ! Yes, it is f. Fill in new object
264     dst displacement %box-displaced-alien/f
265
266     "end" get JMP
267
268     "not-f" resolve-label
269
270     ! Is base an alien?
271     temp alien type-number CMP
272     "not-alien" get JNE
273
274     dst displacement base temp %box-displaced-alien/alien
275
276     ! We are done
277     "end" get JMP
278
279     ! Is base a byte array? It has to be, by now...
280     "not-alien" resolve-label
281
282     dst displacement base temp %box-displaced-alien/byte-array ;
283
284 M:: x86 %box-displaced-alien ( dst displacement base temp base-class -- )
285     [
286         "end" define-label
287
288         ! If displacement is zero, return the base
289         dst base MOV
290         displacement displacement TEST
291         "end" get JE
292
293         ! Displacement is non-zero, we're going to be allocating a new
294         ! object
295         dst 5 cells alien temp %allot
296
297         ! Set expired to f
298         dst 2 alien@ \ f type-number MOV
299
300         dst displacement base temp
301         {
302             { [ base-class \ f class<= ] [ 2drop %box-displaced-alien/f ] }
303             { [ base-class \ alien class<= ] [ %box-displaced-alien/alien ] }
304             { [ base-class \ byte-array class<= ] [ %box-displaced-alien/byte-array ] }
305             [ %box-displaced-alien/dynamic ]
306         } cond
307
308         "end" resolve-label
309     ] with-scope ;
310
311 ! The 'small-reg' mess is pretty crappy, but its only used on x86-32.
312 ! On x86-64, all registers have 8-bit versions. However, a similar
313 ! problem arises for shifts, where the shift count must be in CL, and
314 ! so one day I will fix this properly by adding precoloring to the
315 ! register allocator.
316
317 HOOK: has-small-reg? cpu ( reg size -- ? )
318
319 CONSTANT: have-byte-regs { EAX ECX EDX EBX }
320
321 M: x86.32 has-small-reg?
322     {
323         { 8 [ have-byte-regs member-eq? ] }
324         { 16 [ drop t ] }
325         { 32 [ drop t ] }
326     } case ;
327
328 M: x86.64 has-small-reg? 2drop t ;
329
330 : small-reg-that-isn't ( exclude -- reg' )
331     [ have-byte-regs ] dip
332     [ native-version-of ] map
333     '[ _ member-eq? not ] find nip ;
334
335 : with-save/restore ( reg quot -- )
336     [ drop PUSH ] [ call ] [ drop POP ] 2tri ; inline
337
338 :: with-small-register ( dst exclude size quot: ( new-dst -- ) -- )
339     ! If the destination register overlaps a small register with
340     ! 'size' bits, we call the quot with that. Otherwise, we find a
341     ! small register that is not in exclude, and call quot, saving and
342     ! restoring the small register.
343     dst size has-small-reg? [ dst quot call ] [
344         exclude small-reg-that-isn't
345         [ quot call ] with-save/restore
346     ] if ; inline
347
348 :: %alien-integer-getter ( dst exclude address bits quot -- )
349     dst exclude bits [| new-dst |
350         new-dst dup bits n-bit-version-of dup address MOV
351         quot call
352         dst new-dst int-rep %copy
353     ] with-small-register ; inline
354
355 : %alien-unsigned-getter ( dst exclude address bits -- )
356     [ MOVZX ] %alien-integer-getter ; inline
357
358 : %alien-signed-getter ( dst exclude address bits -- )
359     [ MOVSX ] %alien-integer-getter ; inline
360
361 :: %alien-integer-setter ( value exclude address bits -- )
362     value exclude bits [| new-value |
363         new-value value int-rep %copy
364         address new-value bits n-bit-version-of MOV
365     ] with-small-register ; inline
366
367 : (%memory) ( base displacement scale offset rep c-type -- exclude address rep c-type )
368     [ [ [ 2array ] 2keep ] 2dip <indirect> ] 2dip ;
369
370 : (%memory-imm) ( base offset rep c-type -- exclude address rep c-type )
371     [ [ drop 1array ] [ [+] ] 2bi ] 2dip ;
372
373 : (%load-memory) ( dst exclude address rep c-type -- )
374     [
375         {
376             { c:char   [ 8 %alien-signed-getter ] }
377             { c:uchar  [ 8 %alien-unsigned-getter ] }
378             { c:short  [ 16 %alien-signed-getter ] }
379             { c:ushort [ 16 %alien-unsigned-getter ] }
380             { c:int    [ 32 %alien-signed-getter ] }
381             { c:uint   [ 32 [ 2drop ] %alien-integer-getter ] }
382         } case
383     ] [ [ drop ] 2dip %copy ] ?if ;
384
385 M: x86 %load-memory ( dst base displacement scale offset rep c-type -- )
386     (%memory) (%load-memory) ;
387
388 M: x86 %load-memory-imm ( dst base offset rep c-type -- )
389     (%memory-imm) (%load-memory) ;
390
391 : (%store-memory) ( src exclude address rep c-type -- )
392     [
393         {
394             { c:char   [ 8 %alien-integer-setter ] }
395             { c:uchar  [ 8 %alien-integer-setter ] }
396             { c:short  [ 16 %alien-integer-setter ] }
397             { c:ushort [ 16 %alien-integer-setter ] }
398             { c:int    [ 32 %alien-integer-setter ] }
399             { c:uint   [ 32 %alien-integer-setter ] }
400         } case
401     ] [ [ nip swap ] dip %copy ] ?if ;
402
403 M: x86 %store-memory ( src base displacement scale offset rep c-type -- )
404     (%memory) (%store-memory) ;
405
406 M: x86 %store-memory-imm ( src base offset rep c-type -- )
407     (%memory-imm) (%store-memory) ;
408
409 : shift-count? ( reg -- ? ) { ECX RCX } member-eq? ;
410
411 :: emit-shift ( dst src quot -- )
412     src shift-count? [
413         dst CL quot call
414     ] [
415         dst shift-count? [
416             dst src XCHG
417             src CL quot call
418             dst src XCHG
419         ] [
420             ECX native-version-of [
421                 CL src MOV
422                 drop dst CL quot call
423             ] with-save/restore
424         ] if
425     ] if ; inline
426
427 M: x86 %shl int-rep two-operand [ SHL ] emit-shift ;
428 M: x86 %shr int-rep two-operand [ SHR ] emit-shift ;
429 M: x86 %sar int-rep two-operand [ SAR ] emit-shift ;
430
431 HOOK: %mov-vm-ptr cpu ( reg -- )
432
433 HOOK: %vm-field-ptr cpu ( reg offset -- )
434
435 : load-zone-offset ( nursery-ptr -- )
436     "nursery" vm-field-offset %vm-field-ptr ;
437
438 : load-allot-ptr ( nursery-ptr allot-ptr -- )
439     [ drop load-zone-offset ] [ swap [] MOV ] 2bi ;
440
441 : inc-allot-ptr ( nursery-ptr n -- )
442     [ [] ] dip data-alignment get align ADD ;
443
444 : store-header ( temp class -- )
445     [ [] ] [ type-number tag-header ] bi* MOV ;
446
447 : store-tagged ( dst tag -- )
448     type-number OR ;
449
450 M:: x86 %allot ( dst size class nursery-ptr -- )
451     nursery-ptr dst load-allot-ptr
452     dst class store-header
453     dst class store-tagged
454     nursery-ptr size inc-allot-ptr ;
455
456 HOOK: %mark-card cpu ( card temp -- )
457 HOOK: %mark-deck cpu ( card temp -- )
458
459 :: (%write-barrier) ( temp1 temp2 -- )
460     temp1 card-bits SHR
461     temp1 temp2 %mark-card
462     temp1 deck-bits card-bits - SHR
463     temp1 temp2 %mark-deck ;
464
465 M:: x86 %write-barrier ( src slot scale tag temp1 temp2 -- )
466     temp1 src slot scale tag (%slot) LEA
467     temp1 temp2 (%write-barrier) ;
468
469 M:: x86 %write-barrier-imm ( src slot tag temp1 temp2 -- )
470     temp1 src slot tag (%slot-imm) LEA
471     temp1 temp2 (%write-barrier) ;
472
473 M:: x86 %check-nursery-branch ( label size cc temp1 temp2 -- )
474     temp1 load-zone-offset
475     temp2 temp1 [] MOV
476     temp2 size ADD
477     temp2 temp1 2 cells [+] CMP
478     cc {
479         { cc<= [ label JLE ] }
480         { cc/<= [ label JG ] }
481     } case ;
482
483 : gc-root-offsets ( seq -- seq' )
484     [ n>> spill-offset special-offset cell + cell /i ] map f like ;
485
486 M: x86 %gc-map ( scrub-d scrub-r gc-roots -- )
487     gc-root-offsets 3array set-next-gc-map ;
488
489 M: x86 %call-gc
490     \ minor-gc %call
491     gc-map-here ;
492
493 M: x86 %alien-global ( dst symbol library -- )
494     [ 0 MOV ] 2dip rc-absolute-cell rel-dlsym ;
495
496 M: x86 %epilogue ( n -- ) cell - incr-stack-reg ;
497
498 :: (%boolean) ( dst temp insn -- )
499     dst \ f type-number MOV
500     temp 0 MOV \ t rc-absolute-cell rel-literal
501     dst temp insn execute ; inline
502
503 : %boolean ( dst cc temp -- )
504     swap order-cc {
505         { cc<  [ \ CMOVL (%boolean) ] }
506         { cc<= [ \ CMOVLE (%boolean) ] }
507         { cc>  [ \ CMOVG (%boolean) ] }
508         { cc>= [ \ CMOVGE (%boolean) ] }
509         { cc=  [ \ CMOVE (%boolean) ] }
510         { cc/= [ \ CMOVNE (%boolean) ] }
511     } case ;
512
513 M:: x86 %compare ( dst src1 src2 cc temp -- )
514     src1 src2 CMP
515     dst cc temp %boolean ;
516
517 M:: x86 %test ( dst src1 src2 cc temp -- )
518     src1 src2 TEST
519     dst cc temp %boolean ;
520
521 : (%compare-tagged) ( src1 src2 -- )
522     [ HEX: ffffffff CMP ] dip rc-absolute rel-literal ;
523
524 M:: x86 %compare-integer-imm ( dst src1 src2 cc temp -- )
525     src1 src2 CMP
526     dst cc temp %boolean ;
527
528 M:: x86 %test-imm ( dst src1 src2 cc temp -- )
529     src1 src2 TEST
530     dst cc temp %boolean ;
531
532 : (%compare-imm) ( src1 src2 -- )
533     {
534         { [ dup fixnum? ] [ tag-fixnum CMP ] }
535         { [ dup not ] [ drop \ f type-number CMP ] }
536         [ (%compare-tagged) ]
537     } cond ;
538
539 M:: x86 %compare-imm ( dst src1 src2 cc temp -- )
540     src1 src2 (%compare-imm)
541     dst cc temp %boolean ;
542
543 : %branch ( label cc -- )
544     order-cc {
545         { cc<  [ JL ] }
546         { cc<= [ JLE ] }
547         { cc>  [ JG ] }
548         { cc>= [ JGE ] }
549         { cc=  [ JE ] }
550         { cc/= [ JNE ] }
551     } case ;
552
553 M:: x86 %compare-branch ( label src1 src2 cc -- )
554     src1 src2 CMP
555     label cc %branch ;
556
557 M:: x86 %compare-integer-imm-branch ( label src1 src2 cc -- )
558     src1 src2 CMP
559     label cc %branch ;
560
561 M:: x86 %test-branch ( label src1 src2 cc -- )
562     src1 src2 TEST
563     label cc %branch ;
564
565 M:: x86 %test-imm-branch ( label src1 src2 cc -- )
566     src1 src2 TEST
567     label cc %branch ;
568
569 M:: x86 %compare-imm-branch ( label src1 src2 cc -- )
570     src1 src2 (%compare-imm)
571     label cc %branch ;
572
573 M:: x86 %spill ( src rep dst -- )
574     dst src rep %copy ;
575
576 M:: x86 %reload ( dst rep src -- )
577     dst src rep %copy ;
578
579 M:: x86 %store-stack-param ( src n rep -- )
580     n reserved-stack-space + stack@ src rep %copy ;
581
582 : %load-return ( dst rep -- )
583     [ reg-class-of return-regs at first ] keep %load-reg-param ;
584
585 : %store-return ( dst rep -- )
586     [ reg-class-of return-regs at first ] keep %store-reg-param ;
587
588 : next-stack@ ( n -- operand )
589     #! nth parameter from the next stack frame. Used to box
590     #! input values to callbacks; the callback has its own
591     #! stack frame set up, and we want to read the frame
592     #! set up by the caller.
593     [ frame-reg ] dip 2 cells + reserved-stack-space + [+] ;
594
595 M:: x86 %load-stack-param ( dst n rep -- )
596     dst n next-stack@ rep %copy ;
597
598 M:: x86 %local-allot ( dst size align offset -- )
599     dst offset local-allot-offset special-offset stack@ LEA ;
600
601 M: x86 %alien-indirect ( src -- )
602     ?spill-slot CALL ;
603
604 M: x86 %loop-entry 16 alignment [ NOP ] times ;
605
606 M:: x86 %restore-context ( temp1 temp2 -- )
607     #! Load Factor stack pointers on entry from C to Factor.
608     temp1 %context
609     temp2 stack-reg cell neg [+] LEA
610     temp1 "callstack-top" context-field-offset [+] temp2 MOV
611     ds-reg temp1 "datastack" context-field-offset [+] MOV
612     rs-reg temp1 "retainstack" context-field-offset [+] MOV ;
613
614 M:: x86 %save-context ( temp1 temp2 -- )
615     #! Save Factor stack pointers in case the C code calls a
616     #! callback which does a GC, which must reliably trace
617     #! all roots.
618     temp1 %context
619     temp2 stack-reg cell neg [+] LEA
620     temp1 "callstack-top" context-field-offset [+] temp2 MOV
621     temp1 "datastack" context-field-offset [+] ds-reg MOV
622     temp1 "retainstack" context-field-offset [+] rs-reg MOV ;
623
624 M: x86 value-struct? drop t ;
625
626 M: x86 immediate-arithmetic? ( n -- ? )
627     HEX: -80000000 HEX: 7fffffff between? ;
628
629 M: x86 immediate-bitwise? ( n -- ? )
630     HEX: -80000000 HEX: 7fffffff between? ;
631
632 : %cmov-float= ( dst src -- )
633     [
634         "no-move" define-label
635
636         "no-move" get [ JNE ] [ JP ] bi
637         MOV
638         "no-move" resolve-label
639     ] with-scope ;
640
641 : %cmov-float/= ( dst src -- )
642     [
643         "no-move" define-label
644         "move" define-label
645
646         "move" get JP
647         "no-move" get JE
648         "move" resolve-label
649         MOV
650         "no-move" resolve-label
651     ] with-scope ;
652
653 :: (%compare-float) ( dst src1 src2 cc temp compare -- )
654     cc {
655         { cc<    [ src2 src1 \ compare call( a b -- ) dst temp \ CMOVA  (%boolean) ] }
656         { cc<=   [ src2 src1 \ compare call( a b -- ) dst temp \ CMOVAE (%boolean) ] }
657         { cc>    [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVA  (%boolean) ] }
658         { cc>=   [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVAE (%boolean) ] }
659         { cc=    [ src1 src2 \ compare call( a b -- ) dst temp \ %cmov-float= (%boolean) ] }
660         { cc<>   [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVNE (%boolean) ] }
661         { cc<>=  [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVNP (%boolean) ] }
662         { cc/<   [ src2 src1 \ compare call( a b -- ) dst temp \ CMOVBE (%boolean) ] }
663         { cc/<=  [ src2 src1 \ compare call( a b -- ) dst temp \ CMOVB  (%boolean) ] }
664         { cc/>   [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVBE (%boolean) ] }
665         { cc/>=  [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVB  (%boolean) ] }
666         { cc/=   [ src1 src2 \ compare call( a b -- ) dst temp \ %cmov-float/= (%boolean) ] }
667         { cc/<>  [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVE  (%boolean) ] }
668         { cc/<>= [ src1 src2 \ compare call( a b -- ) dst temp \ CMOVP  (%boolean) ] }
669     } case ; inline
670
671 : %jump-float= ( label -- )
672     [
673         "no-jump" define-label
674         "no-jump" get JP
675         JE
676         "no-jump" resolve-label
677     ] with-scope ;
678
679 : %jump-float/= ( label -- )
680     [ JNE ] [ JP ] bi ;
681
682 :: (%compare-float-branch) ( label src1 src2 cc compare -- )
683     cc {
684         { cc<    [ src2 src1 \ compare call( a b -- ) label JA  ] }
685         { cc<=   [ src2 src1 \ compare call( a b -- ) label JAE ] }
686         { cc>    [ src1 src2 \ compare call( a b -- ) label JA  ] }
687         { cc>=   [ src1 src2 \ compare call( a b -- ) label JAE ] }
688         { cc=    [ src1 src2 \ compare call( a b -- ) label %jump-float= ] }
689         { cc<>   [ src1 src2 \ compare call( a b -- ) label JNE ] }
690         { cc<>=  [ src1 src2 \ compare call( a b -- ) label JNP ] }
691         { cc/<   [ src2 src1 \ compare call( a b -- ) label JBE ] }
692         { cc/<=  [ src2 src1 \ compare call( a b -- ) label JB  ] }
693         { cc/>   [ src1 src2 \ compare call( a b -- ) label JBE ] }
694         { cc/>=  [ src1 src2 \ compare call( a b -- ) label JB  ] }
695         { cc/=   [ src1 src2 \ compare call( a b -- ) label %jump-float/= ] }
696         { cc/<>  [ src1 src2 \ compare call( a b -- ) label JE  ] }
697         { cc/<>= [ src1 src2 \ compare call( a b -- ) label JP  ] }
698     } case ;
699
700 enable-min/max
701 enable-log2
702
703 : check-sse ( -- )
704     "Checking for multimedia extensions... " write flush
705     [ { (sse-version) } compile ] with-optimizer
706     sse-version
707     [ sse-string " detected" append print ]
708     [ 20 < "cpu.x86.x87" "cpu.x86.sse" ? require ] bi ;