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