]> 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, 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@ ( n -- op ) spill-offset param@ ;
34
35 : gc-root@ ( n -- op ) gc-root-offset param@ ;
36
37 : decr-stack-reg ( n -- )
38     dup 0 = [ drop ] [ stack-reg swap SUB ] if ;
39
40 : incr-stack-reg ( n -- )
41     dup 0 = [ drop ] [ stack-reg swap ADD ] if ;
42
43 : align-stack ( n -- n' )
44     os macosx? cpu x86.64? or [ 16 align ] when ;
45
46 M: x86 stack-frame-size ( stack-frame -- i )
47     (stack-frame-size) 3 cells reserved-area-size + + align-stack ;
48
49 ! Must be a volatile register not used for parameter passing, for safe
50 ! use in calls in and out of C
51 HOOK: temp-reg cpu ( -- reg )
52
53 ! Fastcall calling convention
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 :: overflow-template ( label dst src1 src2 insn -- )
130     src1 src2 insn call
131     label JO ; inline
132
133 M: x86 %fixnum-add ( label dst src1 src2 -- )
134     [ ADD ] overflow-template ;
135
136 M: x86 %fixnum-sub ( label dst src1 src2 -- )
137     [ SUB ] overflow-template ;
138
139 M: x86 %fixnum-mul ( label dst src1 src2 -- )
140     [ swap IMUL2 ] overflow-template ;
141
142 : bignum@ ( reg n -- op )
143     cells bignum tag-number - [+] ; inline
144
145 M:: x86 %integer>bignum ( dst src temp -- )
146     #! on entry, inreg is a signed 32-bit quantity
147     #! exits with tagged ptr to bignum in outreg
148     #! 1 cell header, 1 cell length, 1 cell sign, + digits
149     #! length is the # of digits + sign
150     [
151         "end" define-label
152         ! Load cached zero value
153         dst 0 >bignum %load-reference
154         src 0 CMP
155         ! Is it zero? Then just go to the end and return this zero
156         "end" get JE
157         ! Allocate a bignum
158         dst 4 cells bignum temp %allot
159         ! Write length
160         dst 1 bignum@ 2 tag-fixnum MOV
161         ! Store value
162         dst 3 bignum@ src MOV
163         ! Compute sign
164         temp src MOV
165         temp cell-bits 1 - SAR
166         temp 1 AND
167         ! Store sign
168         dst 2 bignum@ temp MOV
169         ! Make negative value positive
170         temp temp ADD
171         temp NEG
172         temp 1 ADD
173         src temp IMUL2
174         ! Store the bignum
175         dst 3 bignum@ temp MOV
176         "end" resolve-label
177     ] with-scope ;
178
179 M:: x86 %bignum>integer ( dst src temp -- )
180     [
181         "end" define-label
182         ! load length
183         temp src 1 bignum@ MOV
184         ! if the length is 1, its just the sign and nothing else,
185         ! so output 0
186         dst 0 MOV
187         temp 1 tag-fixnum CMP
188         "end" get JE
189         ! load the value
190         dst src 3 bignum@ MOV
191         ! load the sign
192         temp src 2 bignum@ MOV
193         ! convert it into -1 or 1
194         temp temp ADD
195         temp NEG
196         temp 1 ADD
197         ! make dst signed
198         temp dst IMUL2
199         "end" resolve-label
200     ] with-scope ;
201
202 M: x86 %add-float nip ADDSD ;
203 M: x86 %sub-float nip SUBSD ;
204 M: x86 %mul-float nip MULSD ;
205 M: x86 %div-float nip DIVSD ;
206 M: x86 %sqrt SQRTSD ;
207
208 M: x86 %integer>float CVTSI2SD ;
209 M: x86 %float>integer CVTTSD2SI ;
210
211 GENERIC: copy-register* ( dst src rep -- )
212
213 M: int-rep copy-register* drop MOV ;
214 M: tagged-rep copy-register* drop MOV ;
215 M: single-float-rep copy-register* drop MOVSS ;
216 M: double-float-rep copy-register* drop MOVSD ;
217
218 : copy-register ( dst src rep -- )
219     2over eq? [ 3drop ] [ copy-register* ] if ;
220
221 M: x86 %copy ( dst src rep -- ) copy-register ;
222
223 M: x86 %unbox-float ( dst src -- )
224     float-offset [+] MOVSD ;
225
226 M:: x86 %unbox-any-c-ptr ( dst src temp -- )
227     [
228         { "is-byte-array" "end" "start" } [ define-label ] each
229         dst 0 MOV
230         temp src MOV
231         ! We come back here with displaced aliens
232         "start" resolve-label
233         ! Is the object f?
234         temp \ f tag-number CMP
235         "end" get JE
236         ! Is the object an alien?
237         temp header-offset [+] alien type-number tag-fixnum CMP
238         "is-byte-array" get JNE
239         ! If so, load the offset and add it to the address
240         dst temp alien-offset [+] ADD
241         ! Now recurse on the underlying alien
242         temp temp underlying-alien-offset [+] MOV
243         "start" get JMP
244         "is-byte-array" resolve-label
245         ! Add byte array address to address being computed
246         dst temp ADD
247         ! Add an offset to start of byte array's data
248         dst byte-array-offset ADD
249         "end" resolve-label
250     ] with-scope ;
251
252 M:: x86 %box-float ( dst src temp -- )
253     dst 16 float temp %allot
254     dst float-offset [+] src MOVSD ;
255
256 : alien@ ( reg n -- op ) cells alien tag-number - [+] ;
257
258 M:: x86 %box-alien ( dst src temp -- )
259     [
260         "end" define-label
261         dst \ f tag-number MOV
262         src 0 CMP
263         "end" get JE
264         dst 4 cells alien temp %allot
265         dst 1 alien@ \ f tag-number MOV
266         dst 2 alien@ \ f tag-number MOV
267         ! Store src in alien-offset slot
268         dst 3 alien@ src MOV
269         "end" resolve-label
270     ] with-scope ;
271
272 ! The 'small-reg' mess is pretty crappy, but its only used on x86-32.
273 ! On x86-64, all registers have 8-bit versions. However, a similar
274 ! problem arises for shifts, where the shift count must be in CL, and
275 ! so one day I will fix this properly by adding precoloring to the
276 ! register allocator.
277
278 HOOK: has-small-reg? cpu ( reg size -- ? )
279
280 CONSTANT: have-byte-regs { EAX ECX EDX EBX }
281
282 M: x86.32 has-small-reg?
283     {
284         { 8 [ have-byte-regs memq? ] }
285         { 16 [ drop t ] }
286         { 32 [ drop t ] }
287     } case ;
288
289 M: x86.64 has-small-reg? 2drop t ;
290
291 : small-reg-that-isn't ( exclude -- reg' )
292     [ have-byte-regs ] dip
293     [ native-version-of ] map
294     '[ _ memq? not ] find nip ;
295
296 : with-save/restore ( reg quot -- )
297     [ drop PUSH ] [ call ] [ drop POP ] 2tri ; inline
298
299 :: with-small-register ( dst exclude size quot: ( new-dst -- ) -- )
300     ! If the destination register overlaps a small register with
301     ! 'size' bits, we call the quot with that. Otherwise, we find a
302     ! small register that is not in exclude, and call quot, saving and
303     ! restoring the small register.
304     dst size has-small-reg? [ dst quot call ] [
305         exclude small-reg-that-isn't
306         [ quot call ] with-save/restore
307     ] if ; inline
308
309 : ?MOV ( dst src -- )
310     2dup = [ 2drop ] [ MOV ] if ; inline
311
312 M:: x86 %string-nth ( dst src index temp -- )
313     ! We request a small-reg of size 8 since those of size 16 are
314     ! a superset.
315     "end" define-label
316     dst { src index temp } 8 [| new-dst |
317         ! Load the least significant 7 bits into new-dst.
318         ! 8th bit indicates whether we have to load from
319         ! the aux vector or not.
320         temp src index [+] LEA
321         new-dst 8-bit-version-of temp string-offset [+] MOV
322         new-dst new-dst 8-bit-version-of MOVZX
323         ! Do we have to look at the aux vector?
324         new-dst HEX: 80 CMP
325         "end" get JL
326         ! Yes, this is a non-ASCII character. Load aux vector
327         temp src string-aux-offset [+] MOV
328         new-dst temp XCHG
329         ! Compute index
330         new-dst index ADD
331         new-dst index ADD
332         ! Load high 16 bits
333         new-dst 16-bit-version-of new-dst byte-array-offset [+] MOV
334         new-dst new-dst 16-bit-version-of MOVZX
335         new-dst 7 SHL
336         ! Compute code point
337         new-dst temp XOR
338         "end" resolve-label
339         dst new-dst ?MOV
340     ] with-small-register ;
341
342 M:: x86 %set-string-nth-fast ( ch str index temp -- )
343     ch { index str temp } 8 [| new-ch |
344         new-ch ch ?MOV
345         temp str index [+] LEA
346         temp string-offset [+] new-ch 8-bit-version-of MOV
347     ] with-small-register ;
348
349 :: %alien-integer-getter ( dst src size quot -- )
350     dst { src } size [| new-dst |
351         new-dst dup size n-bit-version-of dup src [] MOV
352         quot call
353         dst new-dst ?MOV
354     ] with-small-register ; inline
355
356 : %alien-unsigned-getter ( dst src size -- )
357     [ MOVZX ] %alien-integer-getter ; inline
358
359 M: x86 %alien-unsigned-1 8 %alien-unsigned-getter ;
360 M: x86 %alien-unsigned-2 16 %alien-unsigned-getter ;
361 M: x86 %alien-unsigned-4 32 [ 2drop ] %alien-integer-getter ;
362
363 : %alien-signed-getter ( dst src size -- )
364     [ MOVSX ] %alien-integer-getter ; inline
365
366 M: x86 %alien-signed-1 8 %alien-signed-getter ;
367 M: x86 %alien-signed-2 16 %alien-signed-getter ;
368 M: x86 %alien-signed-4 32 %alien-signed-getter ;
369
370 M: x86 %alien-cell [] MOV ;
371 M: x86 %alien-float dupd [] MOVSS dup CVTSS2SD ;
372 M: x86 %alien-double [] MOVSD ;
373
374 :: %alien-integer-setter ( ptr value size -- )
375     value { ptr } size [| new-value |
376         new-value value ?MOV
377         ptr [] new-value size n-bit-version-of MOV
378     ] with-small-register ; inline
379
380 M: x86 %set-alien-integer-1 8 %alien-integer-setter ;
381 M: x86 %set-alien-integer-2 16 %alien-integer-setter ;
382 M: x86 %set-alien-integer-4 32 %alien-integer-setter ;
383 M: x86 %set-alien-cell [ [] ] dip MOV ;
384 M: x86 %set-alien-float dup dup CVTSD2SS [ [] ] dip MOVSS ;
385 M: x86 %set-alien-double [ [] ] dip MOVSD ;
386
387 : shift-count? ( reg -- ? ) { ECX RCX } memq? ;
388
389 :: emit-shift ( dst src1 src2 quot -- )
390     src2 shift-count? [
391         dst CL quot call
392     ] [
393         dst shift-count? [
394             dst src2 XCHG
395             src2 CL quot call
396             dst src2 XCHG
397         ] [
398             ECX native-version-of [
399                 CL src2 MOV
400                 drop dst CL quot call
401             ] with-save/restore
402         ] if
403     ] if ; inline
404
405 M: x86 %shl [ SHL ] emit-shift ;
406 M: x86 %shr [ SHR ] emit-shift ;
407 M: x86 %sar [ SAR ] emit-shift ;
408
409 : load-zone-ptr ( reg -- )
410     #! Load pointer to start of zone array
411     0 MOV "nursery" f rc-absolute-cell rel-dlsym ;
412
413 : load-allot-ptr ( nursery-ptr allot-ptr -- )
414     [ drop load-zone-ptr ] [ swap cell [+] MOV ] 2bi ;
415
416 : inc-allot-ptr ( nursery-ptr n -- )
417     [ cell [+] ] dip 8 align ADD ;
418
419 : store-header ( temp class -- )
420     [ [] ] [ type-number tag-fixnum ] bi* MOV ;
421
422 : store-tagged ( dst tag -- )
423     tag-number OR ;
424
425 M:: x86 %allot ( dst size class nursery-ptr -- )
426     nursery-ptr dst load-allot-ptr
427     dst class store-header
428     dst class store-tagged
429     nursery-ptr size inc-allot-ptr ;
430
431 M:: x86 %write-barrier ( src card# table -- )
432     #! Mark the card pointed to by vreg.
433     ! Mark the card
434     card# src MOV
435     card# card-bits SHR
436     table "cards_offset" f %alien-global
437     table table [] MOV
438     table card# [+] card-mark <byte> MOV
439
440     ! Mark the card deck
441     card# deck-bits card-bits - SHR
442     table "decks_offset" f %alien-global
443     table table [] MOV
444     table card# [+] card-mark <byte> MOV ;
445
446 M:: x86 %check-nursery ( label temp1 temp2 -- )
447     temp1 load-zone-ptr
448     temp2 temp1 cell [+] MOV
449     temp2 1024 ADD
450     temp1 temp1 3 cells [+] MOV
451     temp2 temp1 CMP
452     label JLE ;
453
454 M: x86 %save-gc-root ( gc-root register -- ) [ gc-root@ ] dip MOV ;
455
456 M: x86 %load-gc-root ( gc-root register -- ) swap gc-root@ MOV ;
457
458 M:: x86 %call-gc ( gc-root-count -- )
459     ! Pass pointer to start of GC roots as first parameter
460     param-reg-1 gc-root-base param@ LEA
461     ! Pass number of roots as second parameter
462     param-reg-2 gc-root-count MOV
463     ! Call GC
464     %prepare-alien-invoke
465     "inline_gc" f %alien-invoke ;
466
467 M: x86 %alien-global
468     [ 0 MOV ] 2dip rc-absolute-cell rel-dlsym ;
469
470 M: x86 %epilogue ( n -- ) cell - incr-stack-reg ;
471
472 :: %boolean ( dst temp word -- )
473     dst \ f tag-number MOV
474     temp 0 MOV \ t rc-absolute-cell rel-immediate
475     dst temp word execute ; inline
476
477 M: x86 %compare ( dst temp cc src1 src2 -- )
478     CMP {
479         { cc< [ \ CMOVL %boolean ] }
480         { cc<= [ \ CMOVLE %boolean ] }
481         { cc> [ \ CMOVG %boolean ] }
482         { cc>= [ \ CMOVGE %boolean ] }
483         { cc= [ \ CMOVE %boolean ] }
484         { cc/= [ \ CMOVNE %boolean ] }
485     } case ;
486
487 M: x86 %compare-imm ( dst temp cc src1 src2 -- )
488     %compare ;
489
490 M: x86 %compare-float ( dst temp cc src1 src2 -- )
491     UCOMISD {
492         { cc< [ \ CMOVB %boolean ] }
493         { cc<= [ \ CMOVBE %boolean ] }
494         { cc> [ \ CMOVA %boolean ] }
495         { cc>= [ \ CMOVAE %boolean ] }
496         { cc= [ \ CMOVE %boolean ] }
497         { cc/= [ \ CMOVNE %boolean ] }
498     } case ;
499
500 M: x86 %compare-branch ( label cc src1 src2 -- )
501     CMP {
502         { cc< [ JL ] }
503         { cc<= [ JLE ] }
504         { cc> [ JG ] }
505         { cc>= [ JGE ] }
506         { cc= [ JE ] }
507         { cc/= [ JNE ] }
508     } case ;
509
510 M: x86 %compare-imm-branch ( label src1 src2 cc -- )
511     %compare-branch ;
512
513 M: x86 %compare-float-branch ( label cc src1 src2 -- )
514     UCOMISD {
515         { cc< [ JB ] }
516         { cc<= [ JBE ] }
517         { cc> [ JA ] }
518         { cc>= [ JAE ] }
519         { cc= [ JE ] }
520         { cc/= [ JNE ] }
521     } case ;
522
523 M: x86 %spill ( src n rep -- ) [ spill@ swap ] dip copy-register ;
524 M: x86 %reload ( dst n rep -- ) [ spill@ ] dip copy-register ;
525
526 M: x86 %loop-entry 16 code-alignment [ NOP ] times ;
527
528 M: x86 %prepare-alien-invoke
529     #! Save Factor stack pointers in case the C code calls a
530     #! callback which does a GC, which must reliably trace
531     #! all roots.
532     temp-reg "stack_chain" f %alien-global
533     temp-reg temp-reg [] MOV
534     temp-reg [] stack-reg MOV
535     temp-reg [] cell SUB
536     temp-reg 2 cells [+] ds-reg MOV
537     temp-reg 3 cells [+] rs-reg MOV ;
538
539 M: x86 value-struct? drop t ;
540
541 M: x86 small-enough? ( n -- ? )
542     HEX: -80000000 HEX: 7fffffff between? ;
543
544 : next-stack@ ( n -- operand )
545     #! nth parameter from the next stack frame. Used to box
546     #! input values to callbacks; the callback has its own
547     #! stack frame set up, and we want to read the frame
548     #! set up by the caller.
549     stack-frame get total-size>> + stack@ ;