factor/basis/cpu/x86/x86.factor

575 lines
17 KiB
Factor
Raw Normal View History

2008-04-04 04:46:30 -04:00
! Copyright (C) 2005, 2008 Slava Pestov.
2007-09-20 18:09:08 -04:00
! See http://factorcode.org/license.txt for BSD license.
2008-11-06 02:11:28 -05:00
USING: accessors assocs alien alien.c-types arrays strings
cpu.x86.assembler cpu.x86.assembler.private cpu.x86.assembler.operands
cpu.architecture kernel kernel.private math memory namespaces make
sequences words system layouts combinators math.order fry locals
compiler.constants
compiler.cfg.registers
compiler.cfg.instructions
compiler.cfg.intrinsics
compiler.cfg.comparisons
compiler.cfg.stack-frame
compiler.codegen
compiler.codegen.fixup ;
IN: cpu.x86
2007-09-20 18:09:08 -04:00
<< enable-fixnum-log2 >>
! Add some methods to the assembler to be more useful to the backend
M: label JMP 0 JMP rc-relative label-fixup ;
M: label JUMPcc [ 0 ] dip JUMPcc rc-relative label-fixup ;
2008-10-28 05:38:37 -04:00
M: x86 two-operand? t ;
HOOK: stack-reg cpu ( -- reg )
HOOK: reserved-area-size cpu ( -- n )
: stack@ ( n -- op ) stack-reg swap [+] ;
: param@ ( n -- op ) reserved-area-size + stack@ ;
: spill@ ( n -- op ) spill-offset param@ ;
: gc-root@ ( n -- op ) gc-root-offset param@ ;
: decr-stack-reg ( n -- )
dup 0 = [ drop ] [ stack-reg swap SUB ] if ;
: incr-stack-reg ( n -- )
dup 0 = [ drop ] [ stack-reg swap ADD ] if ;
: align-stack ( n -- n' )
os macosx? cpu x86.64? or [ 16 align ] when ;
M: x86 stack-frame-size ( stack-frame -- i )
(stack-frame-size) 3 cells reserved-area-size + + align-stack ;
! Must be a volatile register not used for parameter passing, for safe
! use in calls in and out of C
HOOK: temp-reg cpu ( -- reg )
2008-10-19 02:10:45 -04:00
! Fastcall calling convention
HOOK: param-reg-1 cpu ( -- reg )
HOOK: param-reg-2 cpu ( -- reg )
HOOK: pic-tail-reg cpu ( -- reg )
M: x86 %load-immediate dup 0 = [ drop dup XOR ] [ MOV ] if ;
2008-10-19 02:10:45 -04:00
M: x86 %load-reference swap 0 MOV rc-absolute-cell rel-immediate ;
2008-10-21 04:21:29 -04:00
2008-10-20 06:55:57 -04:00
HOOK: ds-reg cpu ( -- reg )
HOOK: rs-reg cpu ( -- reg )
2008-10-05 22:30:29 -04:00
2007-09-20 18:09:08 -04:00
: reg-stack ( n reg -- op ) swap cells neg [+] ;
2008-10-07 17:42:11 -04:00
GENERIC: loc>operand ( loc -- operand )
M: ds-loc loc>operand n>> ds-reg reg-stack ;
M: rs-loc loc>operand n>> rs-reg reg-stack ;
2007-09-20 18:09:08 -04:00
2008-10-20 06:55:57 -04:00
M: x86 %peek loc>operand MOV ;
M: x86 %replace loc>operand swap MOV ;
: (%inc) ( n reg -- ) swap cells dup 0 > [ ADD ] [ neg SUB ] if ; inline
M: x86 %inc-d ( n -- ) ds-reg (%inc) ;
M: x86 %inc-r ( n -- ) rs-reg (%inc) ;
2007-09-20 18:09:08 -04:00
M: x86 %call ( word -- ) 0 CALL rc-relative rel-word-pic ;
2009-05-06 23:44:30 -04:00
: xt-tail-pic-offset ( -- n )
#! See the comment in vm/cpu-x86.hpp
cell 4 + 1 + ; inline
M: x86 %jump ( word -- )
2009-05-06 23:44:30 -04:00
pic-tail-reg 0 MOV xt-tail-pic-offset rc-absolute-cell rel-here
0 JMP rc-relative rel-word-pic-tail ;
M: x86 %jump-label ( label -- ) 0 JMP rc-relative label-fixup ;
2008-10-20 06:55:57 -04:00
M: x86 %return ( -- ) 0 RET ;
2008-10-07 17:17:55 -04:00
: code-alignment ( align -- n )
[ building get length dup ] dip align swap - ;
2008-02-09 22:12:00 -05:00
: align-code ( n -- )
0 <repetition> % ;
2008-10-20 06:55:57 -04:00
:: (%slot) ( obj slot tag temp -- op )
temp slot obj [+] LEA
temp tag neg [+] ; inline
:: (%slot-imm) ( obj slot tag -- op )
obj slot cells tag - [+] ; inline
M: x86 %slot ( dst obj slot tag temp -- ) (%slot) MOV ;
M: x86 %slot-imm ( dst obj slot tag -- ) (%slot-imm) MOV ;
M: x86 %set-slot ( src obj slot tag temp -- ) (%slot) swap MOV ;
M: x86 %set-slot-imm ( src obj slot tag -- ) (%slot-imm) swap MOV ;
M: x86 %add 2over eq? [ nip ADD ] [ [+] LEA ] if ;
M: x86 %add-imm 2over eq? [ nip ADD ] [ [+] LEA ] if ;
2008-10-28 05:38:37 -04:00
M: x86 %sub nip SUB ;
M: x86 %sub-imm 2over eq? [ nip SUB ] [ neg [+] LEA ] if ;
2008-10-28 05:38:37 -04:00
M: x86 %mul nip swap IMUL2 ;
M: x86 %mul-imm IMUL3 ;
2008-10-28 05:38:37 -04:00
M: x86 %and nip AND ;
M: x86 %and-imm nip AND ;
M: x86 %or nip OR ;
M: x86 %or-imm nip OR ;
M: x86 %xor nip XOR ;
M: x86 %xor-imm nip XOR ;
M: x86 %shl-imm nip SHL ;
M: x86 %shr-imm nip SHR ;
M: x86 %sar-imm nip SAR ;
M: x86 %not drop NOT ;
M: x86 %log2 BSR ;
2008-10-20 06:55:57 -04:00
:: overflow-template ( label dst src1 src2 insn -- )
src1 src2 insn call
label JO ; inline
M: x86 %fixnum-add ( label dst src1 src2 -- )
[ ADD ] overflow-template ;
M: x86 %fixnum-sub ( label dst src1 src2 -- )
[ SUB ] overflow-template ;
M: x86 %fixnum-mul ( label dst src1 src2 -- )
[ swap IMUL2 ] overflow-template ;
2008-11-30 08:26:49 -05:00
2008-10-20 06:55:57 -04:00
: bignum@ ( reg n -- op )
cells bignum tag-number - [+] ; inline
M:: x86 %integer>bignum ( dst src temp -- )
#! on entry, inreg is a signed 32-bit quantity
#! exits with tagged ptr to bignum in outreg
#! 1 cell header, 1 cell length, 1 cell sign, + digits
#! length is the # of digits + sign
[
"end" define-label
! Load cached zero value
dst 0 >bignum %load-reference
src 0 CMP
! Is it zero? Then just go to the end and return this zero
"end" get JE
2008-10-20 06:55:57 -04:00
! Allocate a bignum
dst 4 cells bignum temp %allot
2008-10-20 06:55:57 -04:00
! Write length
dst 1 bignum@ 2 tag-fixnum MOV
! Store value
2008-10-20 06:55:57 -04:00
dst 3 bignum@ src MOV
! Compute sign
temp src MOV
temp cell-bits 1 - SAR
temp 1 AND
! Store sign
dst 2 bignum@ temp MOV
! Make negative value positive
temp temp ADD
temp NEG
temp 1 ADD
src temp IMUL2
! Store the bignum
dst 3 bignum@ temp MOV
2008-10-20 06:55:57 -04:00
"end" resolve-label
] with-scope ;
M:: x86 %bignum>integer ( dst src temp -- )
2008-10-20 06:55:57 -04:00
[
"end" define-label
! load length
temp src 1 bignum@ MOV
! if the length is 1, its just the sign and nothing else,
! so output 0
2008-10-20 06:55:57 -04:00
dst 0 MOV
temp 1 tag-fixnum CMP
"end" get JE
2008-10-20 06:55:57 -04:00
! load the value
dst src 3 bignum@ MOV
! load the sign
temp src 2 bignum@ MOV
! convert it into -1 or 1
temp temp ADD
temp NEG
temp 1 ADD
! make dst signed
temp dst IMUL2
2008-10-20 06:55:57 -04:00
"end" resolve-label
] with-scope ;
2008-10-28 05:38:37 -04:00
M: x86 %add-float nip ADDSD ;
M: x86 %sub-float nip SUBSD ;
M: x86 %mul-float nip MULSD ;
M: x86 %div-float nip DIVSD ;
M: x86 %sqrt SQRTSD ;
2008-10-22 00:17:32 -04:00
M: x86 %integer>float CVTSI2SD ;
M: x86 %float>integer CVTTSD2SI ;
2007-09-20 18:09:08 -04:00
GENERIC: copy-register* ( dst src rep -- )
2008-10-07 17:17:55 -04:00
M: int-rep copy-register* drop MOV ;
M: tagged-rep copy-register* drop MOV ;
M: single-float-rep copy-register* drop MOVSS ;
M: double-float-rep copy-register* drop MOVSD ;
: copy-register ( dst src rep -- )
2over eq? [ 3drop ] [ copy-register* ] if ;
M: x86 %copy ( dst src rep -- ) copy-register ;
2008-10-20 06:55:57 -04:00
M: x86 %unbox-float ( dst src -- )
float-offset [+] MOVSD ;
2008-10-21 04:21:29 -04:00
M:: x86 %unbox-any-c-ptr ( dst src temp -- )
2008-10-20 06:55:57 -04:00
[
{ "is-byte-array" "end" "start" } [ define-label ] each
dst 0 MOV
temp src MOV
! We come back here with displaced aliens
"start" resolve-label
! Is the object f?
temp \ f tag-number CMP
"end" get JE
! Is the object an alien?
temp header-offset [+] alien type-number tag-fixnum CMP
"is-byte-array" get JNE
! If so, load the offset and add it to the address
dst temp alien-offset [+] ADD
! Now recurse on the underlying alien
temp temp underlying-alien-offset [+] MOV
"start" get JMP
"is-byte-array" resolve-label
! Add byte array address to address being computed
dst temp ADD
! Add an offset to start of byte array's data
dst byte-array-offset ADD
"end" resolve-label
] with-scope ;
M:: x86 %box-float ( dst src temp -- )
dst 16 float temp %allot
2008-10-22 00:17:32 -04:00
dst float-offset [+] src MOVSD ;
2008-10-20 06:55:57 -04:00
: alien@ ( reg n -- op ) cells alien tag-number - [+] ;
2008-10-20 06:55:57 -04:00
:: %allot-alien ( dst base displacement temp -- )
dst 4 cells alien temp %allot
dst 1 alien@ base MOV ! alien
dst 2 alien@ \ f tag-number MOV ! expired
dst 3 alien@ displacement MOV ! displacement
;
2008-10-20 06:55:57 -04:00
M:: x86 %box-alien ( dst src temp -- )
[
"end" define-label
dst \ f tag-number MOV
2008-10-20 06:55:57 -04:00
src 0 CMP
"end" get JE
dst \ f tag-number src temp %allot-alien
"end" resolve-label
] with-scope ;
M:: x86 %box-displaced-alien ( dst displacement base temp -- )
[
"end" define-label
"ok" define-label
! If displacement is zero, return the base
dst base MOV
displacement 0 CMP
"end" get JE
! If base is already a displaced alien, unpack it
base \ f tag-number CMP
"ok" get JE
base header-offset [+] alien type-number tag-fixnum CMP
"ok" get JNE
! displacement += base.displacement
displacement base 3 alien@ ADD
! base = base.base
base base 1 alien@ MOV
"ok" resolve-label
dst base displacement temp %allot-alien
2008-10-20 06:55:57 -04:00
"end" resolve-label
] with-scope ;
! The 'small-reg' mess is pretty crappy, but its only used on x86-32.
! On x86-64, all registers have 8-bit versions. However, a similar
! problem arises for shifts, where the shift count must be in CL, and
! so one day I will fix this properly by adding precoloring to the
! register allocator.
HOOK: has-small-reg? cpu ( reg size -- ? )
CONSTANT: have-byte-regs { EAX ECX EDX EBX }
M: x86.32 has-small-reg?
{
{ 8 [ have-byte-regs memq? ] }
{ 16 [ drop t ] }
{ 32 [ drop t ] }
} case ;
M: x86.64 has-small-reg? 2drop t ;
2008-10-20 06:55:57 -04:00
: small-reg-that-isn't ( exclude -- reg' )
[ have-byte-regs ] dip
[ native-version-of ] map
'[ _ memq? not ] find nip ;
2008-10-20 06:55:57 -04:00
: with-save/restore ( reg quot -- )
[ drop PUSH ] [ call ] [ drop POP ] 2tri ; inline
:: with-small-register ( dst exclude size quot: ( new-dst -- ) -- )
! If the destination register overlaps a small register with
! 'size' bits, we call the quot with that. Otherwise, we find a
! small register that is not in exclude, and call quot, saving and
! restoring the small register.
dst size has-small-reg? [ dst quot call ] [
2008-11-06 02:11:28 -05:00
exclude small-reg-that-isn't
[ quot call ] with-save/restore
2008-10-20 06:55:57 -04:00
] if ; inline
: ?MOV ( dst src -- )
2dup = [ 2drop ] [ MOV ] if ; inline
2008-11-06 02:11:28 -05:00
M:: x86 %string-nth ( dst src index temp -- )
! We request a small-reg of size 8 since those of size 16 are
! a superset.
2008-11-06 02:11:28 -05:00
"end" define-label
dst { src index temp } 8 [| new-dst |
! Load the least significant 7 bits into new-dst.
! 8th bit indicates whether we have to load from
! the aux vector or not.
2008-11-06 02:11:28 -05:00
temp src index [+] LEA
new-dst 8-bit-version-of temp string-offset [+] MOV
new-dst new-dst 8-bit-version-of MOVZX
! Do we have to look at the aux vector?
new-dst HEX: 80 CMP
"end" get JL
! Yes, this is a non-ASCII character. Load aux vector
temp src string-aux-offset [+] MOV
2008-11-06 02:11:28 -05:00
new-dst temp XCHG
! Compute index
2008-11-06 02:11:28 -05:00
new-dst index ADD
new-dst index ADD
! Load high 16 bits
new-dst 16-bit-version-of new-dst byte-array-offset [+] MOV
new-dst new-dst 16-bit-version-of MOVZX
new-dst 7 SHL
! Compute code point
new-dst temp XOR
2008-11-06 02:11:28 -05:00
"end" resolve-label
dst new-dst ?MOV
] with-small-register ;
M:: x86 %set-string-nth-fast ( ch str index temp -- )
ch { index str temp } 8 [| new-ch |
new-ch ch ?MOV
temp str index [+] LEA
temp string-offset [+] new-ch 8-bit-version-of MOV
] with-small-register ;
2008-11-06 02:11:28 -05:00
:: %alien-integer-getter ( dst src size quot -- )
dst { src } size [| new-dst |
new-dst dup size n-bit-version-of dup src [] MOV
2008-11-06 02:11:28 -05:00
quot call
dst new-dst ?MOV
] with-small-register ; inline
2008-10-20 06:55:57 -04:00
: %alien-unsigned-getter ( dst src size -- )
[ MOVZX ] %alien-integer-getter ; inline
M: x86 %alien-unsigned-1 8 %alien-unsigned-getter ;
M: x86 %alien-unsigned-2 16 %alien-unsigned-getter ;
M: x86 %alien-unsigned-4 32 [ 2drop ] %alien-integer-getter ;
2008-10-20 06:55:57 -04:00
: %alien-signed-getter ( dst src size -- )
[ MOVSX ] %alien-integer-getter ; inline
M: x86 %alien-signed-1 8 %alien-signed-getter ;
M: x86 %alien-signed-2 16 %alien-signed-getter ;
M: x86 %alien-signed-4 32 %alien-signed-getter ;
2008-10-22 00:17:32 -04:00
2008-10-20 06:55:57 -04:00
M: x86 %alien-cell [] MOV ;
M: x86 %alien-float dupd [] MOVSS dup CVTSS2SD ;
M: x86 %alien-double [] MOVSD ;
:: %alien-integer-setter ( ptr value size -- )
value { ptr } size [| new-value |
2008-10-20 06:55:57 -04:00
new-value value ?MOV
ptr [] new-value size n-bit-version-of MOV
2008-10-20 06:55:57 -04:00
] with-small-register ; inline
M: x86 %set-alien-integer-1 8 %alien-integer-setter ;
M: x86 %set-alien-integer-2 16 %alien-integer-setter ;
M: x86 %set-alien-integer-4 32 %alien-integer-setter ;
2008-10-20 06:55:57 -04:00
M: x86 %set-alien-cell [ [] ] dip MOV ;
M: x86 %set-alien-float dup dup CVTSD2SS [ [] ] dip MOVSS ;
M: x86 %set-alien-double [ [] ] dip MOVSD ;
: shift-count? ( reg -- ? ) { ECX RCX } memq? ;
:: emit-shift ( dst src1 src2 quot -- )
src2 shift-count? [
dst CL quot call
] [
dst shift-count? [
dst src2 XCHG
src2 CL quot call
dst src2 XCHG
] [
ECX native-version-of [
CL src2 MOV
drop dst CL quot call
] with-save/restore
] if
] if ; inline
M: x86 %shl [ SHL ] emit-shift ;
M: x86 %shr [ SHR ] emit-shift ;
M: x86 %sar [ SAR ] emit-shift ;
2008-10-20 06:55:57 -04:00
: load-zone-ptr ( reg -- )
#! Load pointer to start of zone array
0 MOV "nursery" f rc-absolute-cell rel-dlsym ;
: load-allot-ptr ( nursery-ptr allot-ptr -- )
[ drop load-zone-ptr ] [ swap cell [+] MOV ] 2bi ;
: inc-allot-ptr ( nursery-ptr n -- )
[ cell [+] ] dip 8 align ADD ;
: store-header ( temp class -- )
2008-10-20 06:55:57 -04:00
[ [] ] [ type-number tag-fixnum ] bi* MOV ;
: store-tagged ( dst tag -- )
tag-number OR ;
M:: x86 %allot ( dst size class nursery-ptr -- )
2008-10-20 06:55:57 -04:00
nursery-ptr dst load-allot-ptr
dst class store-header
dst class store-tagged
2008-10-20 06:55:57 -04:00
nursery-ptr size inc-allot-ptr ;
2007-09-20 18:09:08 -04:00
2008-10-20 06:55:57 -04:00
M:: x86 %write-barrier ( src card# table -- )
#! Mark the card pointed to by vreg.
! Mark the card
card# src MOV
card# card-bits SHR
table "cards_offset" f %alien-global
table table [] MOV
2008-10-20 06:55:57 -04:00
table card# [+] card-mark <byte> MOV
! Mark the card deck
card# deck-bits card-bits - SHR
table "decks_offset" f %alien-global
table table [] MOV
2008-10-20 06:55:57 -04:00
table card# [+] card-mark <byte> MOV ;
M:: x86 %check-nursery ( label temp1 temp2 -- )
temp1 load-zone-ptr
temp2 temp1 cell [+] MOV
temp2 1024 ADD
temp1 temp1 3 cells [+] MOV
temp2 temp1 CMP
label JLE ;
M: x86 %save-gc-root ( gc-root register -- ) [ gc-root@ ] dip MOV ;
M: x86 %load-gc-root ( gc-root register -- ) swap gc-root@ MOV ;
M:: x86 %call-gc ( gc-root-count -- )
! Pass pointer to start of GC roots as first parameter
param-reg-1 gc-root-base param@ LEA
! Pass number of roots as second parameter
param-reg-2 gc-root-count MOV
! Call GC
%prepare-alien-invoke
"inline_gc" f %alien-invoke ;
M: x86 %alien-global
[ 0 MOV ] 2dip rc-absolute-cell rel-dlsym ;
2008-10-20 06:55:57 -04:00
M: x86 %epilogue ( n -- ) cell - incr-stack-reg ;
2007-09-20 18:09:08 -04:00
:: %boolean ( dst temp word -- )
dst \ f tag-number MOV
temp 0 MOV \ t rc-absolute-cell rel-immediate
dst temp word execute ; inline
2008-10-21 04:21:29 -04:00
M: x86 %compare ( dst temp cc src1 src2 -- )
2008-10-21 04:21:29 -04:00
CMP {
{ cc< [ \ CMOVL %boolean ] }
{ cc<= [ \ CMOVLE %boolean ] }
{ cc> [ \ CMOVG %boolean ] }
{ cc>= [ \ CMOVGE %boolean ] }
{ cc= [ \ CMOVE %boolean ] }
{ cc/= [ \ CMOVNE %boolean ] }
} case ;
M: x86 %compare-imm ( dst temp cc src1 src2 -- )
2008-10-21 04:21:29 -04:00
%compare ;
M: x86 %compare-float ( dst temp cc src1 src2 -- )
2008-10-21 04:21:29 -04:00
UCOMISD {
{ cc< [ \ CMOVB %boolean ] }
{ cc<= [ \ CMOVBE %boolean ] }
{ cc> [ \ CMOVA %boolean ] }
{ cc>= [ \ CMOVAE %boolean ] }
{ cc= [ \ CMOVE %boolean ] }
{ cc/= [ \ CMOVNE %boolean ] }
} case ;
2008-10-20 06:55:57 -04:00
M: x86 %compare-branch ( label cc src1 src2 -- )
CMP {
{ cc< [ JL ] }
{ cc<= [ JLE ] }
{ cc> [ JG ] }
{ cc>= [ JGE ] }
{ cc= [ JE ] }
2008-10-21 04:21:29 -04:00
{ cc/= [ JNE ] }
2008-10-20 06:55:57 -04:00
} case ;
M: x86 %compare-imm-branch ( label src1 src2 cc -- )
%compare-branch ;
M: x86 %compare-float-branch ( label cc src1 src2 -- )
UCOMISD {
{ cc< [ JB ] }
{ cc<= [ JBE ] }
{ cc> [ JA ] }
{ cc>= [ JAE ] }
{ cc= [ JE ] }
2008-10-21 04:21:29 -04:00
{ cc/= [ JNE ] }
2008-10-20 06:55:57 -04:00
} case ;
2007-09-20 18:09:08 -04:00
M: x86 %spill ( src n rep -- ) [ spill@ swap ] dip copy-register ;
M: x86 %reload ( dst n rep -- ) [ spill@ ] dip copy-register ;
2008-10-20 06:55:57 -04:00
M: x86 %loop-entry 16 code-alignment [ NOP ] times ;
2008-10-20 06:55:57 -04:00
M: x86 %prepare-alien-invoke
#! Save Factor stack pointers in case the C code calls a
#! callback which does a GC, which must reliably trace
#! all roots.
temp-reg "stack_chain" f %alien-global
temp-reg temp-reg [] MOV
temp-reg [] stack-reg MOV
temp-reg [] cell SUB
temp-reg 2 cells [+] ds-reg MOV
temp-reg 3 cells [+] rs-reg MOV ;
2008-10-20 06:55:57 -04:00
2008-11-17 14:34:37 -05:00
M: x86 value-struct? drop t ;
2008-10-20 06:55:57 -04:00
M: x86 small-enough? ( n -- ? )
HEX: -80000000 HEX: 7fffffff between? ;
: next-stack@ ( n -- operand )
#! nth parameter from the next stack frame. Used to box
#! input values to callbacks; the callback has its own
#! stack frame set up, and we want to read the frame
#! set up by the caller.
stack-frame get total-size>> + stack@ ;