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