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