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