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