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