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