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