]> gitweb.factorcode.org Git - factor.git/blob - basis/cpu/x86/x86.factor
cpu.x86: use full set of 8-bit, 16-bit and 32-bit registers on x86-64 to avoid clumsy...
[factor.git] / basis / cpu / x86 / x86.factor
1 ! Copyright (C) 2005, 2008 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.architecture kernel kernel.private math memory namespaces make
6 sequences words system layouts combinators math.order fry locals
7 compiler.constants
8 compiler.cfg.registers
9 compiler.cfg.instructions
10 compiler.cfg.intrinsics
11 compiler.cfg.comparisons
12 compiler.cfg.stack-frame
13 compiler.codegen
14 compiler.codegen.fixup ;
15 IN: cpu.x86
16
17 << enable-fixnum-log2 >>
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 HOOK: stack-reg cpu ( -- reg )
26
27 HOOK: reserved-area-size cpu ( -- n )
28
29 : stack@ ( n -- op ) stack-reg swap [+] ;
30
31 : param@ ( n -- op ) reserved-area-size + stack@ ;
32
33 : spill-integer@ ( n -- op ) spill-integer-offset param@ ;
34
35 : spill-float@ ( n -- op ) spill-float-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 HOOK: temp-reg-1 cpu ( -- reg )
52 HOOK: temp-reg-2 cpu ( -- reg )
53
54 HOOK: param-reg-1 cpu ( -- reg )
55 HOOK: param-reg-2 cpu ( -- reg )
56
57 HOOK: pic-tail-reg cpu ( -- reg )
58
59 M: x86 %load-immediate dup 0 = [ drop dup XOR ] [ MOV ] if ;
60
61 M: x86 %load-reference swap 0 MOV rc-absolute-cell rel-immediate ;
62
63 HOOK: ds-reg cpu ( -- reg )
64 HOOK: rs-reg cpu ( -- reg )
65
66 : reg-stack ( n reg -- op ) swap cells neg [+] ;
67
68 GENERIC: loc>operand ( loc -- operand )
69
70 M: ds-loc loc>operand n>> ds-reg reg-stack ;
71 M: rs-loc loc>operand n>> rs-reg reg-stack ;
72
73 M: x86 %peek loc>operand MOV ;
74 M: x86 %replace loc>operand swap MOV ;
75 : (%inc) ( n reg -- ) swap cells dup 0 > [ ADD ] [ neg SUB ] if ; inline
76 M: x86 %inc-d ( n -- ) ds-reg (%inc) ;
77 M: x86 %inc-r ( n -- ) rs-reg (%inc) ;
78
79 M: x86 %call ( word -- ) 0 CALL rc-relative rel-word-pic ;
80
81 : xt-tail-pic-offset ( -- n )
82     #! See the comment in vm/cpu-x86.hpp
83     cell 4 + 1 + ; inline
84
85 M: x86 %jump ( word -- )
86     pic-tail-reg 0 MOV xt-tail-pic-offset rc-absolute-cell rel-here
87     0 JMP rc-relative rel-word-pic-tail ;
88
89 M: x86 %jump-label ( label -- ) 0 JMP rc-relative label-fixup ;
90
91 M: x86 %return ( -- ) 0 RET ;
92
93 : code-alignment ( align -- n )
94     [ building get length dup ] dip align swap - ;
95
96 : align-code ( n -- )
97     0 <repetition> % ;
98
99 :: (%slot) ( obj slot tag temp -- op )
100     temp slot obj [+] LEA
101     temp tag neg [+] ; inline
102
103 :: (%slot-imm) ( obj slot tag -- op )
104     obj slot cells tag - [+] ; inline
105
106 M: x86 %slot ( dst obj slot tag temp -- ) (%slot) MOV ;
107 M: x86 %slot-imm ( dst obj slot tag -- ) (%slot-imm) MOV ;
108 M: x86 %set-slot ( src obj slot tag temp -- ) (%slot) swap MOV ;
109 M: x86 %set-slot-imm ( src obj slot tag -- ) (%slot-imm) swap MOV ;
110
111 M: x86 %add     2over eq? [ nip ADD ] [ [+] LEA ] if ;
112 M: x86 %add-imm 2over eq? [ nip ADD ] [ [+] LEA ] if ;
113 M: x86 %sub     nip SUB ;
114 M: x86 %sub-imm 2over eq? [ nip SUB ] [ neg [+] LEA ] if ;
115 M: x86 %mul     nip swap IMUL2 ;
116 M: x86 %mul-imm IMUL3 ;
117 M: x86 %and     nip AND ;
118 M: x86 %and-imm nip AND ;
119 M: x86 %or      nip OR ;
120 M: x86 %or-imm  nip OR ;
121 M: x86 %xor     nip XOR ;
122 M: x86 %xor-imm nip XOR ;
123 M: x86 %shl-imm nip SHL ;
124 M: x86 %shr-imm nip SHR ;
125 M: x86 %sar-imm nip SAR ;
126 M: x86 %not     drop NOT ;
127 M: x86 %log2    BSR ;
128
129 : ?MOV ( dst src -- )
130     2dup = [ 2drop ] [ MOV ] if ; inline
131
132 :: overflow-template ( label dst src1 src2 insn -- )
133     src1 src2 insn call
134     label JO ; inline
135
136 M: x86 %fixnum-add ( label dst src1 src2 -- )
137     [ ADD ] overflow-template ;
138
139 M: x86 %fixnum-sub ( label dst src1 src2 -- )
140     [ SUB ] overflow-template ;
141
142 M: x86 %fixnum-mul ( label dst src1 src2 -- )
143     [ swap IMUL2 ] overflow-template ;
144
145 : bignum@ ( reg n -- op )
146     cells bignum tag-number - [+] ; inline
147
148 M:: x86 %integer>bignum ( dst src temp -- )
149     #! on entry, inreg is a signed 32-bit quantity
150     #! exits with tagged ptr to bignum in outreg
151     #! 1 cell header, 1 cell length, 1 cell sign, + digits
152     #! length is the # of digits + sign
153     [
154         "end" define-label
155         ! Load cached zero value
156         dst 0 >bignum %load-reference
157         src 0 CMP
158         ! Is it zero? Then just go to the end and return this zero
159         "end" get JE
160         ! Allocate a bignum
161         dst 4 cells bignum temp %allot
162         ! Write length
163         dst 1 bignum@ 2 tag-fixnum MOV
164         ! Store value
165         dst 3 bignum@ src MOV
166         ! Compute sign
167         temp src MOV
168         temp cell-bits 1- SAR
169         temp 1 AND
170         ! Store sign
171         dst 2 bignum@ temp MOV
172         ! Make negative value positive
173         temp temp ADD
174         temp NEG
175         temp 1 ADD
176         src temp IMUL2
177         ! Store the bignum
178         dst 3 bignum@ temp MOV
179         "end" resolve-label
180     ] with-scope ;
181
182 M:: x86 %bignum>integer ( dst src temp -- )
183     [
184         "end" define-label
185         ! load length
186         temp src 1 bignum@ MOV
187         ! if the length is 1, its just the sign and nothing else,
188         ! so output 0
189         dst 0 MOV
190         temp 1 tag-fixnum CMP
191         "end" get JE
192         ! load the value
193         dst src 3 bignum@ MOV
194         ! load the sign
195         temp src 2 bignum@ MOV
196         ! convert it into -1 or 1
197         temp temp ADD
198         temp NEG
199         temp 1 ADD
200         ! make dst signed
201         temp dst IMUL2
202         "end" resolve-label
203     ] with-scope ;
204
205 M: x86 %add-float nip ADDSD ;
206 M: x86 %sub-float nip SUBSD ;
207 M: x86 %mul-float nip MULSD ;
208 M: x86 %div-float nip DIVSD ;
209
210 M: x86 %integer>float CVTSI2SD ;
211 M: x86 %float>integer CVTTSD2SI ;
212
213 M: x86 %copy ( dst src -- ) ?MOV ;
214
215 M: x86 %copy-float ( dst src -- )
216     2dup = [ 2drop ] [ MOVSD ] if ;
217
218 M: x86 %unbox-float ( dst src -- )
219     float-offset [+] MOVSD ;
220
221 M:: x86 %unbox-any-c-ptr ( dst src temp -- )
222     [
223         { "is-byte-array" "end" "start" } [ define-label ] each
224         dst 0 MOV
225         temp src MOV
226         ! We come back here with displaced aliens
227         "start" resolve-label
228         ! Is the object f?
229         temp \ f tag-number CMP
230         "end" get JE
231         ! Is the object an alien?
232         temp header-offset [+] alien type-number tag-fixnum CMP
233         "is-byte-array" get JNE
234         ! If so, load the offset and add it to the address
235         dst temp alien-offset [+] ADD
236         ! Now recurse on the underlying alien
237         temp temp underlying-alien-offset [+] MOV
238         "start" get JMP
239         "is-byte-array" resolve-label
240         ! Add byte array address to address being computed
241         dst temp ADD
242         ! Add an offset to start of byte array's data
243         dst byte-array-offset ADD
244         "end" resolve-label
245     ] with-scope ;
246
247 M:: x86 %box-float ( dst src temp -- )
248     dst 16 float temp %allot
249     dst float-offset [+] src MOVSD ;
250
251 : alien@ ( reg n -- op ) cells alien tag-number - [+] ;
252
253 M:: x86 %box-alien ( dst src temp -- )
254     [
255         "end" define-label
256         dst \ f tag-number MOV
257         src 0 CMP
258         "end" get JE
259         dst 4 cells alien temp %allot
260         dst 1 alien@ \ f tag-number MOV
261         dst 2 alien@ \ f tag-number MOV
262         ! Store src in alien-offset slot
263         dst 3 alien@ src MOV
264         "end" resolve-label
265     ] with-scope ;
266
267 HOOK: small-reg? cpu ( reg -- regs )
268
269 M: x86.32 small-reg? { EAX ECX EDX EBX } memq? ;
270 M: x86.64 small-reg? drop t ;
271
272 : small-reg-that-isn't ( exclude -- reg' )
273     [ native-version-of ] map [ small-reg? not ] find nip ;
274
275 : with-save/restore ( reg quot -- )
276     [ drop PUSH ] [ call ] [ drop POP ] 2tri ; inline
277
278 :: with-small-register ( dst exclude quot: ( new-dst -- ) -- )
279     #! If the destination register overlaps a small register, we
280     #! call the quot with that. Otherwise, we find a small
281     #! register that is not in exclude, and call quot, saving
282     #! and restoring the small register.
283     dst small-reg? [ dst quot call ] [
284         exclude small-reg-that-isn't
285         [ quot call ] with-save/restore
286     ] if ; inline
287
288 : shift-count? ( reg -- ? ) { ECX RCX } memq? ;
289
290 :: emit-shift ( dst src1 src2 quot -- )
291     src2 shift-count? [
292         dst CL quot call
293     ] [
294         dst shift-count? [
295             dst src2 XCHG
296             src2 CL quot call
297             dst src2 XCHG
298         ] [
299             ECX native-version-of [
300                 CL src2 MOV
301                 drop dst CL quot call
302             ] with-save/restore
303         ] if
304     ] if ; inline
305
306 M: x86 %shl [ SHL ] emit-shift ;
307 M: x86 %shr [ SHR ] emit-shift ;
308 M: x86 %sar [ SAR ] emit-shift ;
309
310 M:: x86 %string-nth ( dst src index temp -- )
311     "end" define-label
312     dst { src index temp } [| new-dst |
313         ! Load the least significant 7 bits into new-dst.
314         ! 8th bit indicates whether we have to load from
315         ! the aux vector or not.
316         temp src index [+] LEA
317         new-dst 8-bit-version-of temp string-offset [+] MOV
318         new-dst new-dst 8-bit-version-of MOVZX
319         ! Do we have to look at the aux vector?
320         new-dst HEX: 80 CMP
321         "end" get JL
322         ! Yes, this is a non-ASCII character. Load aux vector
323         temp src string-aux-offset [+] MOV
324         new-dst temp XCHG
325         ! Compute index
326         new-dst index ADD
327         new-dst index ADD
328         ! Load high 16 bits
329         new-dst 16-bit-version-of new-dst byte-array-offset [+] MOV
330         new-dst new-dst 16-bit-version-of MOVZX
331         new-dst 7 SHL
332         ! Compute code point
333         new-dst temp XOR
334         "end" resolve-label
335         dst new-dst ?MOV
336     ] with-small-register ;
337
338 M:: x86 %set-string-nth-fast ( ch str index temp -- )
339     ch { index str temp } [| new-ch |
340         new-ch ch ?MOV
341         temp str index [+] LEA
342         temp string-offset [+] new-ch 8-bit-version-of MOV
343     ] with-small-register ;
344
345 :: %alien-integer-getter ( dst src size quot -- )
346     dst { src } [| new-dst |
347         new-dst dup size 8 * n-bit-version-of dup src [] MOV
348         quot call
349         dst new-dst ?MOV
350     ] with-small-register ; inline
351
352 : %alien-unsigned-getter ( dst src size -- )
353     [ MOVZX ] %alien-integer-getter ; inline
354
355 M: x86 %alien-unsigned-1 1 %alien-unsigned-getter ;
356 M: x86 %alien-unsigned-2 2 %alien-unsigned-getter ;
357
358 : %alien-signed-getter ( dst src size -- )
359     [ MOVSX ] %alien-integer-getter ; inline
360
361 M: x86 %alien-signed-1 1 %alien-signed-getter ;
362 M: x86 %alien-signed-2 2 %alien-signed-getter ;
363 M: x86 %alien-signed-4 4 %alien-signed-getter ;
364
365 M: x86 %alien-unsigned-4 4 [ 2drop ] %alien-integer-getter ;
366
367 M: x86 %alien-cell [] MOV ;
368 M: x86 %alien-float dupd [] MOVSS dup CVTSS2SD ;
369 M: x86 %alien-double [] MOVSD ;
370
371 :: %alien-integer-setter ( ptr value size -- )
372     value { ptr } [| new-value |
373         new-value value ?MOV
374         ptr [] new-value size 8 * n-bit-version-of MOV
375     ] with-small-register ; inline
376
377 M: x86 %set-alien-integer-1 1 %alien-integer-setter ;
378 M: x86 %set-alien-integer-2 2 %alien-integer-setter ;
379 M: x86 %set-alien-integer-4 4 %alien-integer-setter ;
380 M: x86 %set-alien-cell [ [] ] dip MOV ;
381 M: x86 %set-alien-float dup dup CVTSD2SS [ [] ] dip MOVSS ;
382 M: x86 %set-alien-double [ [] ] dip MOVSD ;
383
384 : load-zone-ptr ( reg -- )
385     #! Load pointer to start of zone array
386     0 MOV "nursery" f rc-absolute-cell rel-dlsym ;
387
388 : load-allot-ptr ( nursery-ptr allot-ptr -- )
389     [ drop load-zone-ptr ] [ swap cell [+] MOV ] 2bi ;
390
391 : inc-allot-ptr ( nursery-ptr n -- )
392     [ cell [+] ] dip 8 align ADD ;
393
394 : store-header ( temp class -- )
395     [ [] ] [ type-number tag-fixnum ] bi* MOV ;
396
397 : store-tagged ( dst tag -- )
398     tag-number OR ;
399
400 M:: x86 %allot ( dst size class nursery-ptr -- )
401     nursery-ptr dst load-allot-ptr
402     dst class store-header
403     dst class store-tagged
404     nursery-ptr size inc-allot-ptr ;
405
406 M:: x86 %write-barrier ( src card# table -- )
407     #! Mark the card pointed to by vreg.
408     ! Mark the card
409     card# src MOV
410     card# card-bits SHR
411     table "cards_offset" f %alien-global
412     table table [] MOV
413     table card# [+] card-mark <byte> MOV
414
415     ! Mark the card deck
416     card# deck-bits card-bits - SHR
417     table "decks_offset" f %alien-global
418     table table [] MOV
419     table card# [+] card-mark <byte> MOV ;
420
421 :: check-nursery ( temp1 temp2 -- )
422     temp1 load-zone-ptr
423     temp2 temp1 cell [+] MOV
424     temp2 1024 ADD
425     temp1 temp1 3 cells [+] MOV
426     temp2 temp1 CMP ;
427
428 GENERIC# save-gc-root 1 ( gc-root operand temp -- )
429
430 M:: spill-slot save-gc-root ( gc-root spill-slot temp -- )
431     temp spill-slot n>> spill-integer@ MOV
432     gc-root gc-root@ temp MOV ;
433
434 M:: word save-gc-root ( gc-root register temp -- )
435     gc-root gc-root@ register MOV ;
436
437 : save-gc-roots ( gc-roots temp -- )
438     '[ _ save-gc-root ] assoc-each ;
439
440 GENERIC# load-gc-root 1 ( gc-root operand temp -- )
441
442 M:: spill-slot load-gc-root ( gc-root spill-slot temp -- )
443     temp gc-root gc-root@ MOV
444     spill-slot n>> spill-integer@ temp MOV ;
445
446 M:: word load-gc-root ( gc-root register temp -- )
447     register gc-root gc-root@ MOV ;
448
449 : load-gc-roots ( gc-roots temp -- )
450     '[ _ load-gc-root ] assoc-each ;
451
452 :: call-gc ( gc-root-count -- )
453     ! Pass pointer to start of GC roots as first parameter
454     param-reg-1 gc-root-base param@ LEA
455     ! Pass number of roots as second parameter
456     param-reg-2 gc-root-count MOV
457     ! Call GC
458     %prepare-alien-invoke
459     "inline_gc" f %alien-invoke ;
460
461 M:: x86 %gc ( temp1 temp2 gc-roots gc-root-count -- )
462     "end" define-label
463     temp1 temp2 check-nursery
464     "end" get JLE
465     gc-roots temp1 save-gc-roots
466     gc-root-count call-gc
467     gc-roots temp1 load-gc-roots
468     "end" resolve-label ;
469
470 M: x86 %alien-global
471     [ 0 MOV ] 2dip rc-absolute-cell rel-dlsym ;
472
473 M: x86 %epilogue ( n -- ) cell - incr-stack-reg ;
474
475 :: %boolean ( dst temp word -- )
476     dst \ f tag-number MOV
477     temp 0 MOV \ t rc-absolute-cell rel-immediate
478     dst temp word execute ; inline
479
480 M: x86 %compare ( dst temp cc src1 src2 -- )
481     CMP {
482         { cc< [ \ CMOVL %boolean ] }
483         { cc<= [ \ CMOVLE %boolean ] }
484         { cc> [ \ CMOVG %boolean ] }
485         { cc>= [ \ CMOVGE %boolean ] }
486         { cc= [ \ CMOVE %boolean ] }
487         { cc/= [ \ CMOVNE %boolean ] }
488     } case ;
489
490 M: x86 %compare-imm ( dst temp cc src1 src2 -- )
491     %compare ;
492
493 M: x86 %compare-float ( dst temp cc src1 src2 -- )
494     UCOMISD {
495         { cc< [ \ CMOVB %boolean ] }
496         { cc<= [ \ CMOVBE %boolean ] }
497         { cc> [ \ CMOVA %boolean ] }
498         { cc>= [ \ CMOVAE %boolean ] }
499         { cc= [ \ CMOVE %boolean ] }
500         { cc/= [ \ CMOVNE %boolean ] }
501     } case ;
502
503 M: x86 %compare-branch ( label cc src1 src2 -- )
504     CMP {
505         { cc< [ JL ] }
506         { cc<= [ JLE ] }
507         { cc> [ JG ] }
508         { cc>= [ JGE ] }
509         { cc= [ JE ] }
510         { cc/= [ JNE ] }
511     } case ;
512
513 M: x86 %compare-imm-branch ( label src1 src2 cc -- )
514     %compare-branch ;
515
516 M: x86 %compare-float-branch ( label cc src1 src2 -- )
517     UCOMISD {
518         { cc< [ JB ] }
519         { cc<= [ JBE ] }
520         { cc> [ JA ] }
521         { cc>= [ JAE ] }
522         { cc= [ JE ] }
523         { cc/= [ JNE ] }
524     } case ;
525
526 M: x86 %spill-integer ( src n -- ) spill-integer@ swap MOV ;
527 M: x86 %reload-integer ( dst n -- ) spill-integer@ MOV ;
528
529 M: x86 %spill-float ( src n -- ) spill-float@ swap MOVSD ;
530 M: x86 %reload-float ( dst n -- ) spill-float@ MOVSD ;
531
532 M: x86 %loop-entry 16 code-alignment [ NOP ] times ;
533
534 M: int-regs %save-param-reg drop [ param@ ] dip MOV ;
535 M: int-regs %load-param-reg drop swap param@ MOV ;
536
537 GENERIC: MOVSS/D ( dst src reg-class -- )
538
539 M: single-float-regs MOVSS/D drop MOVSS ;
540 M: double-float-regs MOVSS/D drop MOVSD ;
541
542 M: float-regs %save-param-reg [ param@ ] 2dip MOVSS/D ;
543 M: float-regs %load-param-reg [ swap param@ ] dip MOVSS/D ;
544
545 GENERIC: push-return-reg ( reg-class -- )
546 GENERIC: load-return-reg ( n reg-class -- )
547 GENERIC: store-return-reg ( n reg-class -- )
548
549 M: x86 %prepare-alien-invoke
550     #! Save Factor stack pointers in case the C code calls a
551     #! callback which does a GC, which must reliably trace
552     #! all roots.
553     temp-reg-1 "stack_chain" f %alien-global
554     temp-reg-1 temp-reg-1 [] MOV
555     temp-reg-1 [] stack-reg MOV
556     temp-reg-1 [] cell SUB
557     temp-reg-1 2 cells [+] ds-reg MOV
558     temp-reg-1 3 cells [+] rs-reg MOV ;
559
560 M: x86 value-struct? drop t ;
561
562 M: x86 small-enough? ( n -- ? )
563     HEX: -80000000 HEX: 7fffffff between? ;
564
565 : next-stack@ ( n -- operand )
566     #! nth parameter from the next stack frame. Used to box
567     #! input values to callbacks; the callback has its own
568     #! stack frame set up, and we want to read the frame
569     #! set up by the caller.
570     stack-frame get total-size>> + stack@ ;