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