]> gitweb.factorcode.org Git - factor.git/blob - basis/cpu/x86/x86.factor
Fix conflict
[factor.git] / basis / cpu / x86 / x86.factor
1 ! Copyright (C) 2005, 2009 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.architecture kernel kernel.private math memory namespaces make
6 sequences words system layouts combinators math.order fry locals
7 compiler.constants byte-arrays io macros quotations cpu.x86.features
8 cpu.x86.features.private compiler compiler.units init
9 compiler.constants vm byte-arrays
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 FROM: layouts => cell ;
17 FROM: math => float ;
18 IN: cpu.x86
19
20 ! Add some methods to the assembler to be more useful to the backend
21 M: label JMP 0 JMP rc-relative label-fixup ;
22 M: label JUMPcc [ 0 ] dip JUMPcc rc-relative label-fixup ;
23
24 M: x86 two-operand? t ;
25
26 HOOK: stack-reg cpu ( -- reg )
27
28 HOOK: reserved-area-size cpu ( -- n )
29
30 : stack@ ( n -- op ) stack-reg swap [+] ;
31
32 : param@ ( n -- op ) reserved-area-size + stack@ ;
33
34 : spill@ ( n -- op ) spill-offset param@ ;
35
36 : gc-root@ ( n -- op ) gc-root-offset param@ ;
37
38 : decr-stack-reg ( n -- )
39     dup 0 = [ drop ] [ stack-reg swap SUB ] if ;
40
41 : incr-stack-reg ( n -- )
42     dup 0 = [ drop ] [ stack-reg swap ADD ] if ;
43
44 : align-stack ( n -- n' )
45     os macosx? cpu x86.64? or [ 16 align ] when ;
46
47 M: x86 stack-frame-size ( stack-frame -- i )
48     (stack-frame-size) 3 cells reserved-area-size + + align-stack ;
49
50 ! Must be a volatile register not used for parameter passing, for safe
51 ! use in calls in and out of C
52 HOOK: temp-reg cpu ( -- reg )
53
54 ! Fastcall calling convention
55 HOOK: param-reg-1 cpu ( -- reg )
56 HOOK: param-reg-2 cpu ( -- reg )
57
58 HOOK: pic-tail-reg cpu ( -- reg )
59
60 M: x86 %load-immediate dup 0 = [ drop dup XOR ] [ MOV ] if ;
61
62 M: x86 %load-reference swap 0 MOV rc-absolute-cell rel-immediate ;
63
64 HOOK: ds-reg cpu ( -- reg )
65 HOOK: rs-reg cpu ( -- reg )
66
67 : reg-stack ( n reg -- op ) swap cells neg [+] ;
68
69 GENERIC: loc>operand ( loc -- operand )
70
71 M: ds-loc loc>operand n>> ds-reg reg-stack ;
72 M: rs-loc loc>operand n>> rs-reg reg-stack ;
73
74 M: x86 %peek loc>operand MOV ;
75 M: x86 %replace loc>operand swap MOV ;
76 : (%inc) ( n reg -- ) swap cells dup 0 > [ ADD ] [ neg SUB ] if ; inline
77 M: x86 %inc-d ( n -- ) ds-reg (%inc) ;
78 M: x86 %inc-r ( n -- ) rs-reg (%inc) ;
79
80 M: x86 %call ( word -- ) 0 CALL rc-relative rel-word-pic ;
81
82 : xt-tail-pic-offset ( -- n )
83     #! See the comment in vm/cpu-x86.hpp
84     cell 4 + 1 + ; inline
85
86 M: x86 %jump ( word -- )
87     pic-tail-reg 0 MOV xt-tail-pic-offset rc-absolute-cell rel-here
88     0 JMP rc-relative rel-word-pic-tail ;
89
90 M: x86 %jump-label ( label -- ) 0 JMP rc-relative label-fixup ;
91
92 M: x86 %return ( -- ) 0 RET ;
93
94 : code-alignment ( align -- n )
95     [ building get length dup ] dip align swap - ;
96
97 : align-code ( n -- )
98     0 <repetition> % ;
99
100 :: (%slot) ( obj slot tag temp -- op )
101     temp slot obj [+] LEA
102     temp tag neg [+] ; inline
103
104 :: (%slot-imm) ( obj slot tag -- op )
105     obj slot cells tag - [+] ; inline
106
107 M: x86 %slot ( dst obj slot tag temp -- ) (%slot) MOV ;
108 M: x86 %slot-imm ( dst obj slot tag -- ) (%slot-imm) MOV ;
109 M: x86 %set-slot ( src obj slot tag temp -- ) (%slot) swap MOV ;
110 M: x86 %set-slot-imm ( src obj slot tag -- ) (%slot-imm) swap MOV ;
111
112 M: x86 %add     2over eq? [ nip ADD ] [ [+] LEA ] if ;
113 M: x86 %add-imm 2over eq? [ nip ADD ] [ [+] LEA ] if ;
114 M: x86 %sub     nip SUB ;
115 M: x86 %sub-imm 2over eq? [ nip SUB ] [ neg [+] LEA ] if ;
116 M: x86 %mul     nip swap IMUL2 ;
117 M: x86 %mul-imm IMUL3 ;
118 M: x86 %and     nip AND ;
119 M: x86 %and-imm nip AND ;
120 M: x86 %or      nip OR ;
121 M: x86 %or-imm  nip OR ;
122 M: x86 %xor     nip XOR ;
123 M: x86 %xor-imm nip XOR ;
124 M: x86 %shl-imm nip SHL ;
125 M: x86 %shr-imm nip SHR ;
126 M: x86 %sar-imm nip SAR ;
127
128 M: x86 %min     nip [ CMP ] [ CMOVG ] 2bi ;
129 M: x86 %max     nip [ CMP ] [ CMOVL ] 2bi ;
130
131 M: x86 %not     drop NOT ;
132 M: x86 %log2    BSR ;
133
134 GENERIC: copy-register* ( dst src rep -- )
135
136 M: int-rep copy-register* drop MOV ;
137 M: tagged-rep copy-register* drop MOV ;
138 M: float-rep copy-register* drop MOVSS ;
139 M: double-rep copy-register* drop MOVSD ;
140 M: float-4-rep copy-register* drop MOVUPS ;
141 M: double-2-rep copy-register* drop MOVUPD ;
142 M: vector-rep copy-register* drop MOVDQU ;
143
144 : copy-register ( dst src rep -- )
145     2over eq? [ 3drop ] [ copy-register* ] if ;
146
147 M: x86 %copy ( dst src rep -- ) copy-register ;
148
149 :: overflow-template ( label dst src1 src2 insn -- )
150     src1 src2 insn call
151     label JO ; inline
152
153 M: x86 %fixnum-add ( label dst src1 src2 -- )
154     [ ADD ] overflow-template ;
155
156 M: x86 %fixnum-sub ( label dst src1 src2 -- )
157     [ SUB ] overflow-template ;
158
159 M: x86 %fixnum-mul ( label dst src1 src2 -- )
160     [ swap IMUL2 ] overflow-template ;
161
162 : bignum@ ( reg n -- op )
163     cells bignum tag-number - [+] ; inline
164
165 M:: x86 %integer>bignum ( dst src temp -- )
166     #! on entry, inreg is a signed 32-bit quantity
167     #! exits with tagged ptr to bignum in outreg
168     #! 1 cell header, 1 cell length, 1 cell sign, + digits
169     #! length is the # of digits + sign
170     [
171         "end" define-label
172         ! Load cached zero value
173         dst 0 >bignum %load-reference
174         src 0 CMP
175         ! Is it zero? Then just go to the end and return this zero
176         "end" get JE
177         ! Allocate a bignum
178         dst 4 cells bignum temp %allot
179         ! Write length
180         dst 1 bignum@ 2 tag-fixnum MOV
181         ! Store value
182         dst 3 bignum@ src MOV
183         ! Compute sign
184         temp src MOV
185         temp cell-bits 1 - SAR
186         temp 1 AND
187         ! Store sign
188         dst 2 bignum@ temp MOV
189         ! Make negative value positive
190         temp temp ADD
191         temp NEG
192         temp 1 ADD
193         src temp IMUL2
194         ! Store the bignum
195         dst 3 bignum@ temp MOV
196         "end" resolve-label
197     ] with-scope ;
198
199 M:: x86 %bignum>integer ( dst src temp -- )
200     [
201         "end" define-label
202         ! load length
203         temp src 1 bignum@ MOV
204         ! if the length is 1, its just the sign and nothing else,
205         ! so output 0
206         dst 0 MOV
207         temp 1 tag-fixnum CMP
208         "end" get JE
209         ! load the value
210         dst src 3 bignum@ MOV
211         ! load the sign
212         temp src 2 bignum@ MOV
213         ! convert it into -1 or 1
214         temp temp ADD
215         temp NEG
216         temp 1 ADD
217         ! make dst signed
218         temp dst IMUL2
219         "end" resolve-label
220     ] with-scope ;
221
222 M: x86 %add-float nip ADDSD ;
223 M: x86 %sub-float nip SUBSD ;
224 M: x86 %mul-float nip MULSD ;
225 M: x86 %div-float nip DIVSD ;
226 M: x86 %min-float nip MINSD ;
227 M: x86 %max-float nip MAXSD ;
228 M: x86 %sqrt SQRTSD ;
229
230 M: x86 %single>double-float CVTSS2SD ;
231 M: x86 %double>single-float CVTSD2SS ;
232
233 M: x86 %integer>float CVTSI2SD ;
234 M: x86 %float>integer CVTTSD2SI ;
235
236 M: x86 %unbox-float ( dst src -- )
237     float-offset [+] MOVSD ;
238
239 M:: x86 %box-float ( dst src temp -- )
240     dst 16 float temp %allot
241     dst float-offset [+] src MOVSD ;
242
243 M:: x86 %box-vector ( dst src rep temp -- )
244     dst rep rep-size 2 cells + byte-array temp %allot
245     16 tag-fixnum dst 1 byte-array tag-number %set-slot-imm
246     dst byte-array-offset [+]
247     src rep copy-register ;
248
249 M:: x86 %unbox-vector ( dst src rep -- )
250     dst src byte-array-offset [+]
251     rep copy-register ;
252
253 MACRO: available-reps ( alist -- )
254     ! Each SSE version adds new representations and supports
255     ! all old ones
256     unzip { } [ append ] accumulate rest swap suffix
257     [ [ 1quotation ] map ] bi@ zip
258     reverse [ { } ] suffix
259     '[ _ cond ] ;
260
261 M: x86 %broadcast-vector ( dst src rep -- )
262     {
263         { float-4-rep [ [ MOVSS ] [ drop dup 0 SHUFPS ] 2bi ] }
264         { double-2-rep [ [ MOVSD ] [ drop dup UNPCKLPD ] 2bi ] }
265     } case ;
266
267 M: x86 %broadcast-vector-reps
268     {
269         { sse? { float-4-rep } }
270         { sse2? { double-2-rep } }
271     } available-reps ;
272
273 M:: x86 %gather-vector-4 ( dst src1 src2 src3 src4 rep -- )
274     rep {
275         {
276             float-4-rep
277             [
278                 dst src1 MOVSS
279                 dst src2 UNPCKLPS
280                 src3 src4 UNPCKLPS
281                 dst src3 MOVLHPS
282             ]
283         }
284     } case ;
285
286 M: x86 %gather-vector-4-reps
287     {
288         { sse? { float-4-rep } }
289     } available-reps ;
290
291 M:: x86 %gather-vector-2 ( dst src1 src2 rep -- )
292     rep {
293         {
294             double-2-rep
295             [
296                 dst src1 MOVSD
297                 dst src2 UNPCKLPD
298             ]
299         }
300     } case ;
301
302 M: x86 %gather-vector-2-reps
303     {
304         { sse2? { double-2-rep } }
305     } available-reps ;
306
307 M: x86 %add-vector ( dst src1 src2 rep -- )
308     {
309         { float-4-rep [ ADDPS ] }
310         { double-2-rep [ ADDPD ] }
311         { char-16-rep [ PADDB ] }
312         { uchar-16-rep [ PADDB ] }
313         { short-8-rep [ PADDW ] }
314         { ushort-8-rep [ PADDW ] }
315         { int-4-rep [ PADDD ] }
316         { uint-4-rep [ PADDD ] }
317     } case drop ;
318
319 M: x86 %add-vector-reps
320     {
321         { sse? { float-4-rep } }
322         { sse2? { double-2-rep char-16-rep uchar-16-rep short-8-rep ushort-8-rep int-4-rep uint-4-rep } }
323     } available-reps ;
324
325 M: x86 %saturated-add-vector ( dst src1 src2 rep -- )
326     {
327         { char-16-rep [ PADDSB ] }
328         { uchar-16-rep [ PADDUSB ] }
329         { short-8-rep [ PADDSW ] }
330         { ushort-8-rep [ PADDUSW ] }
331     } case drop ;
332
333 M: x86 %saturated-add-vector-reps
334     {
335         { sse2? { char-16-rep uchar-16-rep short-8-rep ushort-8-rep } }
336     } available-reps ;
337
338 M: x86 %add-sub-vector ( dst src1 src2 rep -- )
339     {
340         { float-4-rep [ ADDSUBPS ] }
341         { double-2-rep [ ADDSUBPD ] }
342     } case drop ;
343
344 M: x86 %add-sub-vector-reps
345     {
346         { sse3? { float-4-rep double-2-rep } }
347     } available-reps ;
348
349 M: x86 %sub-vector ( dst src1 src2 rep -- )
350     {
351         { float-4-rep [ SUBPS ] }
352         { double-2-rep [ SUBPD ] }
353         { char-16-rep [ PSUBB ] }
354         { uchar-16-rep [ PSUBB ] }
355         { short-8-rep [ PSUBW ] }
356         { ushort-8-rep [ PSUBW ] }
357         { int-4-rep [ PSUBD ] }
358         { uint-4-rep [ PSUBD ] }
359     } case drop ;
360
361 M: x86 %sub-vector-reps
362     {
363         { sse? { float-4-rep } }
364         { sse2? { double-2-rep char-16-rep uchar-16-rep short-8-rep ushort-8-rep int-4-rep uint-4-rep } }
365     } available-reps ;
366
367 M: x86 %saturated-sub-vector ( dst src1 src2 rep -- )
368     {
369         { char-16-rep [ PSUBSB ] }
370         { uchar-16-rep [ PSUBUSB ] }
371         { short-8-rep [ PSUBSW ] }
372         { ushort-8-rep [ PSUBUSW ] }
373     } case drop ;
374
375 M: x86 %saturated-sub-vector-reps
376     {
377         { sse2? { char-16-rep uchar-16-rep short-8-rep ushort-8-rep } }
378     } available-reps ;
379
380 M: x86 %mul-vector ( dst src1 src2 rep -- )
381     {
382         { float-4-rep [ MULPS ] }
383         { double-2-rep [ MULPD ] }
384         { short-8-rep [ PMULLW ] }
385         { ushort-8-rep [ PMULLW ] }
386         { int-4-rep [ PMULLD ] }
387         { uint-4-rep [ PMULLD ] }
388     } case drop ;
389
390 M: x86 %mul-vector-reps
391     {
392         { sse? { float-4-rep } }
393         { sse2? { double-2-rep short-8-rep ushort-8-rep int-4-rep uint-4-rep } }
394     } available-reps ;
395
396 M: x86 %saturated-mul-vector-reps
397     ! No multiplication with saturation on x86
398     { } ;
399
400 M: x86 %div-vector ( dst src1 src2 rep -- )
401     {
402         { float-4-rep [ DIVPS ] }
403         { double-2-rep [ DIVPD ] }
404     } case drop ;
405
406 M: x86 %div-vector-reps
407     {
408         { sse? { float-4-rep } }
409         { sse2? { double-2-rep } }
410     } available-reps ;
411
412 M: x86 %min-vector ( dst src1 src2 rep -- )
413     {
414         { float-4-rep [ MINPS ] }
415         { double-2-rep [ MINPD ] }
416         { uchar-16-rep [ PMINUB ] }
417         { short-8-rep [ PMINSW ] }
418     } case drop ;
419
420 M: x86 %min-vector-reps
421     {
422         { sse? { float-4-rep } }
423         { sse2? { double-2-rep short-8-rep uchar-16-rep } }
424     } available-reps ;
425
426 M: x86 %max-vector ( dst src1 src2 rep -- )
427     {
428         { float-4-rep [ MAXPS ] }
429         { double-2-rep [ MAXPD ] }
430         { uchar-16-rep [ PMAXUB ] }
431         { short-8-rep [ PMAXSW ] }
432     } case drop ;
433
434 M: x86 %max-vector-reps
435     {
436         { sse? { float-4-rep } }
437         { sse2? { double-2-rep short-8-rep uchar-16-rep } }
438     } available-reps ;
439
440 M: x86 %sqrt-vector ( dst src rep -- )
441     {
442         { float-4-rep [ SQRTPS ] }
443         { double-2-rep [ SQRTPD ] }
444     } case ;
445
446 M: x86 %sqrt-vector-reps
447     {
448         { sse? { float-4-rep } }
449         { sse2? { double-2-rep } }
450     } available-reps ;
451
452 M: x86 %horizontal-add-vector ( dst src rep -- )
453     {
454         { float-4-rep [ [ MOVAPS ] [ HADDPS ] [ HADDPS ] 2tri ] }
455         { double-2-rep [ [ MOVAPD ] [ HADDPD ] 2bi ] }
456     } case ;
457
458 M: x86 %horizontal-add-vector-reps
459     {
460         { sse3? { float-4-rep double-2-rep } }
461     } available-reps ;
462
463 M: x86 %unbox-alien ( dst src -- )
464     alien-offset [+] MOV ;
465
466 M:: x86 %unbox-any-c-ptr ( dst src temp -- )
467     [
468         { "is-byte-array" "end" "start" } [ define-label ] each
469         dst 0 MOV
470         temp src MOV
471         ! We come back here with displaced aliens
472         "start" resolve-label
473         ! Is the object f?
474         temp \ f tag-number CMP
475         "end" get JE
476         ! Is the object an alien?
477         temp header-offset [+] alien type-number tag-fixnum CMP
478         "is-byte-array" get JNE
479         ! If so, load the offset and add it to the address
480         dst temp alien-offset [+] ADD
481         ! Now recurse on the underlying alien
482         temp temp underlying-alien-offset [+] MOV
483         "start" get JMP
484         "is-byte-array" resolve-label
485         ! Add byte array address to address being computed
486         dst temp ADD
487         ! Add an offset to start of byte array's data
488         dst byte-array-offset ADD
489         "end" resolve-label
490     ] with-scope ;
491
492 : alien@ ( reg n -- op ) cells alien tag-number - [+] ;
493
494 :: %allot-alien ( dst displacement base temp -- )
495     dst 4 cells alien temp %allot
496     dst 1 alien@ base MOV ! alien
497     dst 2 alien@ \ f tag-number MOV ! expired
498     dst 3 alien@ displacement MOV ! displacement
499     ;
500
501 M:: x86 %box-alien ( dst src temp -- )
502     [
503         "end" define-label
504         dst \ f tag-number MOV
505         src 0 CMP
506         "end" get JE
507         dst src \ f tag-number temp %allot-alien
508         "end" resolve-label
509     ] with-scope ;
510
511 M:: x86 %box-displaced-alien ( dst displacement base displacement' base' base-class -- )
512     [
513         "end" define-label
514         "ok" define-label
515         ! If displacement is zero, return the base
516         dst base MOV
517         displacement 0 CMP
518         "end" get JE
519         ! Quickly use displacement' before its needed for real, as allot temporary
520         dst 4 cells alien displacement' %allot
521         ! If base is already a displaced alien, unpack it
522         base' base MOV
523         displacement' displacement MOV
524         base \ f tag-number CMP
525         "ok" get JE
526         base header-offset [+] alien type-number tag-fixnum CMP
527         "ok" get JNE
528         ! displacement += base.displacement
529         displacement' base 3 alien@ ADD
530         ! base = base.base
531         base' base 1 alien@ MOV
532         "ok" resolve-label
533         dst 1 alien@ base' MOV ! alien
534         dst 2 alien@ \ f tag-number MOV ! expired
535         dst 3 alien@ displacement' MOV ! displacement
536         "end" resolve-label
537     ] with-scope ;
538
539 ! The 'small-reg' mess is pretty crappy, but its only used on x86-32.
540 ! On x86-64, all registers have 8-bit versions. However, a similar
541 ! problem arises for shifts, where the shift count must be in CL, and
542 ! so one day I will fix this properly by adding precoloring to the
543 ! register allocator.
544
545 HOOK: has-small-reg? cpu ( reg size -- ? )
546
547 CONSTANT: have-byte-regs { EAX ECX EDX EBX }
548
549 M: x86.32 has-small-reg?
550     {
551         { 8 [ have-byte-regs memq? ] }
552         { 16 [ drop t ] }
553         { 32 [ drop t ] }
554     } case ;
555
556 M: x86.64 has-small-reg? 2drop t ;
557
558 : small-reg-that-isn't ( exclude -- reg' )
559     [ have-byte-regs ] dip
560     [ native-version-of ] map
561     '[ _ memq? not ] find nip ;
562
563 : with-save/restore ( reg quot -- )
564     [ drop PUSH ] [ call ] [ drop POP ] 2tri ; inline
565
566 :: with-small-register ( dst exclude size quot: ( new-dst -- ) -- )
567     ! If the destination register overlaps a small register with
568     ! 'size' bits, we call the quot with that. Otherwise, we find a
569     ! small register that is not in exclude, and call quot, saving and
570     ! restoring the small register.
571     dst size has-small-reg? [ dst quot call ] [
572         exclude small-reg-that-isn't
573         [ quot call ] with-save/restore
574     ] if ; inline
575
576 : ?MOV ( dst src -- )
577     2dup = [ 2drop ] [ MOV ] if ; inline
578
579 M:: x86 %string-nth ( dst src index temp -- )
580     ! We request a small-reg of size 8 since those of size 16 are
581     ! a superset.
582     "end" define-label
583     dst { src index temp } 8 [| new-dst |
584         ! Load the least significant 7 bits into new-dst.
585         ! 8th bit indicates whether we have to load from
586         ! the aux vector or not.
587         temp src index [+] LEA
588         new-dst 8-bit-version-of temp string-offset [+] MOV
589         new-dst new-dst 8-bit-version-of MOVZX
590         ! Do we have to look at the aux vector?
591         new-dst HEX: 80 CMP
592         "end" get JL
593         ! Yes, this is a non-ASCII character. Load aux vector
594         temp src string-aux-offset [+] MOV
595         new-dst temp XCHG
596         ! Compute index
597         new-dst index ADD
598         new-dst index ADD
599         ! Load high 16 bits
600         new-dst 16-bit-version-of new-dst byte-array-offset [+] MOV
601         new-dst new-dst 16-bit-version-of MOVZX
602         new-dst 7 SHL
603         ! Compute code point
604         new-dst temp XOR
605         "end" resolve-label
606         dst new-dst ?MOV
607     ] with-small-register ;
608
609 M:: x86 %set-string-nth-fast ( ch str index temp -- )
610     ch { index str temp } 8 [| new-ch |
611         new-ch ch ?MOV
612         temp str index [+] LEA
613         temp string-offset [+] new-ch 8-bit-version-of MOV
614     ] with-small-register ;
615
616 :: %alien-integer-getter ( dst src size quot -- )
617     dst { src } size [| new-dst |
618         new-dst dup size n-bit-version-of dup src [] MOV
619         quot call
620         dst new-dst ?MOV
621     ] with-small-register ; inline
622
623 : %alien-unsigned-getter ( dst src size -- )
624     [ MOVZX ] %alien-integer-getter ; inline
625
626 M: x86 %alien-unsigned-1 8 %alien-unsigned-getter ;
627 M: x86 %alien-unsigned-2 16 %alien-unsigned-getter ;
628 M: x86 %alien-unsigned-4 32 [ 2drop ] %alien-integer-getter ;
629
630 : %alien-signed-getter ( dst src size -- )
631     [ MOVSX ] %alien-integer-getter ; inline
632
633 M: x86 %alien-signed-1 8 %alien-signed-getter ;
634 M: x86 %alien-signed-2 16 %alien-signed-getter ;
635 M: x86 %alien-signed-4 32 %alien-signed-getter ;
636
637 M: x86 %alien-cell [] MOV ;
638 M: x86 %alien-float [] MOVSS ;
639 M: x86 %alien-double [] MOVSD ;
640 M: x86 %alien-vector [ [] ] dip copy-register ;
641
642 :: %alien-integer-setter ( ptr value size -- )
643     value { ptr } size [| new-value |
644         new-value value ?MOV
645         ptr [] new-value size n-bit-version-of MOV
646     ] with-small-register ; inline
647
648 M: x86 %set-alien-integer-1 8 %alien-integer-setter ;
649 M: x86 %set-alien-integer-2 16 %alien-integer-setter ;
650 M: x86 %set-alien-integer-4 32 %alien-integer-setter ;
651 M: x86 %set-alien-cell [ [] ] dip MOV ;
652 M: x86 %set-alien-float [ [] ] dip MOVSS ;
653 M: x86 %set-alien-double [ [] ] dip MOVSD ;
654 M: x86 %set-alien-vector [ [] ] 2dip copy-register ;
655
656 : shift-count? ( reg -- ? ) { ECX RCX } memq? ;
657
658 :: emit-shift ( dst src1 src2 quot -- )
659     src2 shift-count? [
660         dst CL quot call
661     ] [
662         dst shift-count? [
663             dst src2 XCHG
664             src2 CL quot call
665             dst src2 XCHG
666         ] [
667             ECX native-version-of [
668                 CL src2 MOV
669                 drop dst CL quot call
670             ] with-save/restore
671         ] if
672     ] if ; inline
673
674 M: x86 %shl [ SHL ] emit-shift ;
675 M: x86 %shr [ SHR ] emit-shift ;
676 M: x86 %sar [ SAR ] emit-shift ;
677
678 M: x86 %vm-field-ptr ( dst field -- )
679     [ drop 0 MOV rc-absolute-cell rt-vm rel-fixup ]
680     [ vm-field-offset ADD ] 2bi ;
681
682 : load-zone-ptr ( reg -- )
683     #! Load pointer to start of zone array
684     "nursery" %vm-field-ptr ;
685
686 : load-allot-ptr ( nursery-ptr allot-ptr -- )
687     [ drop load-zone-ptr ] [ swap cell [+] MOV ] 2bi ;
688
689 : inc-allot-ptr ( nursery-ptr n -- )
690     [ cell [+] ] dip 8 align ADD ;
691
692 : store-header ( temp class -- )
693     [ [] ] [ type-number tag-fixnum ] bi* MOV ;
694
695 : store-tagged ( dst tag -- )
696     tag-number OR ;
697
698 M:: x86 %allot ( dst size class nursery-ptr -- )
699     nursery-ptr dst load-allot-ptr
700     dst class store-header
701     dst class store-tagged
702     nursery-ptr size inc-allot-ptr ;
703
704
705 M:: x86 %write-barrier ( src card# table -- )
706     #! Mark the card pointed to by vreg.
707     ! Mark the card
708     card# src MOV
709     card# card-bits SHR
710     table "cards_offset" %vm-field-ptr
711     table table [] MOV
712     table card# [+] card-mark <byte> MOV
713
714     ! Mark the card deck
715     card# deck-bits card-bits - SHR
716     table "decks_offset" %vm-field-ptr
717     table table [] MOV
718     table card# [+] card-mark <byte> MOV ;
719
720 M:: x86 %check-nursery ( label temp1 temp2 -- )
721     temp1 load-zone-ptr
722     temp2 temp1 cell [+] MOV
723     temp2 1024 ADD
724     temp1 temp1 3 cells [+] MOV
725     temp2 temp1 CMP
726     label JLE ;
727
728 M: x86 %save-gc-root ( gc-root register -- ) [ gc-root@ ] dip MOV ;
729
730 M: x86 %load-gc-root ( gc-root register -- ) swap gc-root@ MOV ;
731
732 M:: x86 %call-gc ( gc-root-count -- )
733     ! Pass pointer to start of GC roots as first parameter
734     param-reg-1 gc-root-base param@ LEA
735     ! Pass number of roots as second parameter
736     param-reg-2 gc-root-count MOV
737     ! Call GC
738     "inline_gc" %vm-invoke-3rd-arg ; 
739
740 M: x86 %alien-global ( dst symbol library -- )
741     [ 0 MOV ] 2dip rc-absolute-cell rel-dlsym ;    
742
743 M: x86 %epilogue ( n -- ) cell - incr-stack-reg ;
744
745 :: %boolean ( dst temp word -- )
746     dst \ f tag-number MOV
747     temp 0 MOV \ t rc-absolute-cell rel-immediate
748     dst temp word execute ; inline
749
750 M:: x86 %compare ( dst src1 src2 cc temp -- )
751     src1 src2 CMP
752     cc order-cc {
753         { cc<  [ dst temp \ CMOVL %boolean ] }
754         { cc<= [ dst temp \ CMOVLE %boolean ] }
755         { cc>  [ dst temp \ CMOVG %boolean ] }
756         { cc>= [ dst temp \ CMOVGE %boolean ] }
757         { cc=  [ dst temp \ CMOVE %boolean ] }
758         { cc/= [ dst temp \ CMOVNE %boolean ] }
759     } case ;
760
761 M: x86 %compare-imm ( dst src1 src2 cc temp -- )
762     %compare ;
763
764 : %cmov-float= ( dst src -- )
765     [
766         "no-move" define-label
767
768         "no-move" get [ JNE ] [ JP ] bi
769         MOV
770         "no-move" resolve-label
771     ] with-scope ;
772
773 : %cmov-float/= ( dst src -- )
774     [
775         "no-move" define-label
776         "move" define-label
777
778         "move" get JP
779         "no-move" get JE
780         "move" resolve-label
781         MOV
782         "no-move" resolve-label
783     ] with-scope ;
784
785 :: (%compare-float) ( dst src1 src2 cc temp compare -- )
786     cc {
787         { cc<    [ src2 src1 \ compare execute( a b -- ) dst temp \ CMOVA  %boolean ] }
788         { cc<=   [ src2 src1 \ compare execute( a b -- ) dst temp \ CMOVAE %boolean ] }
789         { cc>    [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVA  %boolean ] }
790         { cc>=   [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVAE %boolean ] }
791         { cc=    [ src1 src2 \ compare execute( a b -- ) dst temp \ %cmov-float= %boolean ] }
792         { cc<>   [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVNE %boolean ] }
793         { cc<>=  [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVNP %boolean ] }
794         { cc/<   [ src2 src1 \ compare execute( a b -- ) dst temp \ CMOVBE %boolean ] }
795         { cc/<=  [ src2 src1 \ compare execute( a b -- ) dst temp \ CMOVB  %boolean ] }
796         { cc/>   [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVBE %boolean ] }
797         { cc/>=  [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVB  %boolean ] }
798         { cc/=   [ src1 src2 \ compare execute( a b -- ) dst temp \ %cmov-float/= %boolean ] }
799         { cc/<>  [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVE  %boolean ] }
800         { cc/<>= [ src1 src2 \ compare execute( a b -- ) dst temp \ CMOVP  %boolean ] }
801     } case ; inline
802
803 M: x86 %compare-float-ordered ( dst src1 src2 cc temp -- )
804     \ COMISD (%compare-float) ;
805
806 M: x86 %compare-float-unordered ( dst src1 src2 cc temp -- )
807     \ UCOMISD (%compare-float) ;
808
809 M:: x86 %compare-branch ( label src1 src2 cc -- )
810     src1 src2 CMP
811     cc order-cc {
812         { cc<  [ label JL ] }
813         { cc<= [ label JLE ] }
814         { cc>  [ label JG ] }
815         { cc>= [ label JGE ] }
816         { cc=  [ label JE ] }
817         { cc/= [ label JNE ] }
818     } case ;
819
820 M: x86 %compare-imm-branch ( label src1 src2 cc -- )
821     %compare-branch ;
822
823 : %jump-float= ( label -- )
824     [
825         "no-jump" define-label
826         "no-jump" get JP
827         JE
828         "no-jump" resolve-label
829     ] with-scope ;
830
831 : %jump-float/= ( label -- )
832     [ JNE ] [ JP ] bi ;
833
834 :: (%compare-float-branch) ( label src1 src2 cc compare -- )
835     cc {
836         { cc<    [ src2 src1 \ compare execute( a b -- ) label JA  ] }
837         { cc<=   [ src2 src1 \ compare execute( a b -- ) label JAE ] }
838         { cc>    [ src1 src2 \ compare execute( a b -- ) label JA  ] }
839         { cc>=   [ src1 src2 \ compare execute( a b -- ) label JAE ] }
840         { cc=    [ src1 src2 \ compare execute( a b -- ) label %jump-float= ] }
841         { cc<>   [ src1 src2 \ compare execute( a b -- ) label JNE ] }
842         { cc<>=  [ src1 src2 \ compare execute( a b -- ) label JNP ] }
843         { cc/<   [ src2 src1 \ compare execute( a b -- ) label JBE ] }
844         { cc/<=  [ src2 src1 \ compare execute( a b -- ) label JB  ] }
845         { cc/>   [ src1 src2 \ compare execute( a b -- ) label JBE ] }
846         { cc/>=  [ src1 src2 \ compare execute( a b -- ) label JB  ] }
847         { cc/=   [ src1 src2 \ compare execute( a b -- ) label %jump-float/= ] }
848         { cc/<>  [ src1 src2 \ compare execute( a b -- ) label JE  ] }
849         { cc/<>= [ src1 src2 \ compare execute( a b -- ) label JP  ] }
850     } case ;
851
852 M: x86 %compare-float-ordered-branch ( label src1 src2 cc -- )
853     \ COMISD (%compare-float-branch) ;
854
855 M: x86 %compare-float-unordered-branch ( label src1 src2 cc -- )
856     \ UCOMISD (%compare-float-branch) ;
857
858 M:: x86 %spill ( src rep n -- )
859     n spill@ src rep copy-register ;
860
861 M:: x86 %reload ( dst rep n -- )
862     dst n spill@ rep copy-register ;
863
864 M: x86 %loop-entry 16 code-alignment [ NOP ] times ;
865
866 M:: x86 %save-context ( temp1 temp2 callback-allowed? -- )
867     #! Save Factor stack pointers in case the C code calls a
868     #! callback which does a GC, which must reliably trace
869     #! all roots.
870     temp1 0 MOV rc-absolute-cell rt-vm rel-fixup
871     temp1 temp1 "stack_chain" vm-field-offset [+] MOV
872     temp2 stack-reg cell neg [+] LEA
873     temp1 [] temp2 MOV
874     callback-allowed? [
875         temp1 2 cells [+] ds-reg MOV
876         temp1 3 cells [+] rs-reg MOV
877     ] when ;
878
879 M: x86 value-struct? drop t ;
880
881 M: x86 small-enough? ( n -- ? )
882     HEX: -80000000 HEX: 7fffffff between? ;
883
884 : next-stack@ ( n -- operand )
885     #! nth parameter from the next stack frame. Used to box
886     #! input values to callbacks; the callback has its own
887     #! stack frame set up, and we want to read the frame
888     #! set up by the caller.
889     stack-frame get total-size>> + stack@ ;
890
891 enable-simd
892 enable-min/max
893 enable-fixnum-log2
894
895 :: install-sse2-check ( -- )
896     [
897         sse-version 20 < [
898             "This image was built to use SSE2 but your CPU does not support it." print
899             "You will need to bootstrap Factor again." print
900             flush
901             1 exit
902         ] when
903     ] "cpu.x86" add-init-hook ;
904
905 : enable-sse2 ( version -- )
906     20 >= [
907         enable-float-intrinsics
908         enable-fsqrt
909         enable-float-min/max
910         install-sse2-check
911     ] when ;
912
913 : check-sse ( -- )
914     [ { sse_version } compile ] with-optimizer
915     "Checking for multimedia extensions: " write sse-version
916     [ sse-string write " detected" print ] [ enable-sse2 ] bi ;