]> gitweb.factorcode.org Git - factor.git/blob - basis/cpu/x86/32/32.factor
compiler: add ##load-vector instruction to avoid wasting a temporary register on...
[factor.git] / basis / cpu / x86 / 32 / 32.factor
1 ! Copyright (C) 2005, 2010 Slava Pestov.
2 ! See http://factorcode.org/license.txt for BSD license.
3 USING: locals alien alien.c-types alien.libraries alien.syntax
4 arrays kernel fry math namespaces sequences system layouts io
5 vocabs.loader accessors init classes.struct combinators
6 command-line make words compiler compiler.units
7 compiler.constants compiler.alien compiler.codegen
8 compiler.codegen.fixup compiler.cfg.instructions
9 compiler.cfg.builder compiler.cfg.intrinsics
10 compiler.cfg.stack-frame cpu.x86.assembler
11 cpu.x86.assembler.operands cpu.x86 cpu.architecture vm ;
12 FROM: layouts => cell ;
13 IN: cpu.x86.32
14
15 M: x86.32 machine-registers
16     {
17         { int-regs { EAX ECX EDX EBP EBX } }
18         { float-regs { XMM0 XMM1 XMM2 XMM3 XMM4 XMM5 XMM6 XMM7 } }
19     } ;
20
21 M: x86.32 ds-reg ESI ;
22 M: x86.32 rs-reg EDI ;
23 M: x86.32 stack-reg ESP ;
24 M: x86.32 frame-reg EBP ;
25 M: x86.32 temp-reg ECX ;
26
27 M: x86.32 immediate-comparand? ( n -- ? )
28     [ call-next-method ] [ word? ] bi or ;
29
30 M: x86.32 object-immediates? ( -- ? ) t ;
31
32 M: x86.32 %load-double ( dst val -- )
33     [ 0 [] MOVSD ] dip rc-absolute rel-float ;
34
35 M:: x86.32 %load-vector ( dst val rep -- )
36     dst 0 [] rep copy-memory* val rc-absolute rel-byte-array ;
37
38 M: x86.32 %mov-vm-ptr ( reg -- )
39     0 MOV 0 rc-absolute-cell rel-vm ;
40
41 M: x86.32 %vm-field ( dst field -- )
42     [ 0 [] MOV ] dip rc-absolute-cell rel-vm ;
43
44 M: x86.32 %set-vm-field ( dst field -- )
45     [ 0 [] swap MOV ] dip rc-absolute-cell rel-vm ;
46
47 M: x86.32 %vm-field-ptr ( dst field -- )
48     [ 0 MOV ] dip rc-absolute-cell rel-vm ;
49
50 : local@ ( n -- op )
51     stack-frame get extra-stack-space dup 16 assert= + stack@ ;
52
53 M: x86.32 extra-stack-space calls-vm?>> 16 0 ? ;
54
55 M: x86.32 %mark-card
56     drop HEX: ffffffff [+] card-mark <byte> MOV
57     building get pop
58     rc-absolute-cell rel-cards-offset
59     building get push ;
60
61 M: x86.32 %mark-deck
62     drop HEX: ffffffff [+] card-mark <byte> MOV
63     building get pop
64     rc-absolute-cell rel-decks-offset
65     building get push ;
66
67 M:: x86.32 %dispatch ( src temp -- )
68     ! Load jump table base.
69     temp src HEX: ffffffff [+] LEA
70     building get length :> start
71     0 rc-absolute-cell rel-here
72     ! Go
73     temp HEX: 7f [+] JMP
74     building get length :> end
75     ! Fix up the displacement above
76     cell code-alignment
77     [ end start - + building get dup pop* push ]
78     [ align-code ]
79     bi ;
80
81 M: x86.32 pic-tail-reg EDX ;
82
83 M: x86.32 reserved-stack-space 0 ;
84
85 M: x86.32 %alien-invoke 0 CALL rc-relative rel-dlsym ;
86
87 : save-vm-ptr ( n -- )
88     stack@ 0 MOV 0 rc-absolute-cell rel-vm ;
89
90 M: x86.32 return-struct-in-registers? ( c-type -- ? )
91     c-type
92     [ return-in-registers?>> ]
93     [ heap-size { 1 2 4 8 } member? ] bi
94     os { linux netbsd solaris } member? not
95     and or ;
96
97 : struct-return@ ( n -- operand )
98     [ next-stack@ ] [ stack-frame get params>> local@ ] if* ;
99
100 ! On x86, parameters are usually never passed in registers, except with Microsoft's
101 ! "thiscall" and "fastcall" abis
102 M: int-regs return-reg drop EAX ;
103 M: float-regs param-regs 2drop { } ;
104
105 M: int-regs param-regs
106     nip {
107         { thiscall [ { ECX     } ] }
108         { fastcall [ { ECX EDX } ] }
109         [ drop { } ]
110     } case ;
111
112 GENERIC: load-return-reg ( src rep -- )
113 GENERIC: store-return-reg ( dst rep -- )
114
115 M: stack-params load-return-reg drop EAX swap MOV ;
116 M: stack-params store-return-reg drop EAX MOV ;
117
118 M: int-rep load-return-reg drop EAX swap MOV ;
119 M: int-rep store-return-reg drop EAX MOV ;
120
121 M: float-rep load-return-reg drop FLDS ;
122 M: float-rep store-return-reg drop FSTPS ;
123
124 M: double-rep load-return-reg drop FLDL ;
125 M: double-rep store-return-reg drop FSTPL ;
126
127 M: x86.32 %prologue ( n -- )
128     dup PUSH
129     0 PUSH rc-absolute-cell rel-this
130     3 cells - decr-stack-reg ;
131
132 M: x86.32 %prepare-jump
133     pic-tail-reg 0 MOV xt-tail-pic-offset rc-absolute-cell rel-here ;
134
135 M: stack-params copy-register*
136     drop
137     {
138         { [ dup  integer? ] [ EAX swap next-stack@ MOV  EAX MOV ] }
139         { [ over integer? ] [ EAX swap MOV              param@ EAX MOV ] }
140     } cond ;
141
142 M: x86.32 %save-param-reg [ local@ ] 2dip %copy ;
143
144 M: x86.32 %load-param-reg [ swap local@ ] dip %copy ;
145
146 : (%box) ( n rep -- )
147     #! If n is f, push the return register onto the stack; we
148     #! are boxing a return value of a C function. If n is an
149     #! integer, push [ESP+n] on the stack; we are boxing a
150     #! parameter being passed to a callback from C.
151     over [ [ local@ ] dip load-return-reg ] [ 2drop ] if ;
152
153 M:: x86.32 %box ( n rep func -- )
154     n rep (%box)
155     rep rep-size save-vm-ptr
156     0 stack@ rep store-return-reg
157     func f %alien-invoke ;
158
159 : (%box-long-long) ( n -- )
160     [
161         EDX over next-stack@ MOV
162         EAX swap cell - next-stack@ MOV 
163     ] when* ;
164
165 M: x86.32 %box-long-long ( n func -- )
166     [ (%box-long-long) ] dip
167     8 save-vm-ptr
168     4 stack@ EDX MOV
169     0 stack@ EAX MOV
170     f %alien-invoke ;
171
172 M:: x86.32 %box-large-struct ( n c-type -- )
173     EDX n struct-return@ LEA
174     8 save-vm-ptr
175     4 stack@ c-type heap-size MOV
176     0 stack@ EDX MOV
177     "from_value_struct" f %alien-invoke ;
178
179 M: x86.32 %prepare-box-struct ( -- )
180     ! Compute target address for value struct return
181     EAX f struct-return@ LEA
182     ! Store it as the first parameter
183     0 local@ EAX MOV ;
184
185 M: x86.32 %box-small-struct ( c-type -- )
186     #! Box a <= 8-byte struct returned in EAX:EDX. OS X only.
187     12 save-vm-ptr
188     8 stack@ swap heap-size MOV
189     4 stack@ EDX MOV
190     0 stack@ EAX MOV
191     "from_small_struct" f %alien-invoke ;
192
193 M: x86.32 %pop-stack ( n -- )
194     EAX swap ds-reg reg-stack MOV ;
195
196 M: x86.32 %pop-context-stack ( -- )
197     temp-reg %context
198     EAX temp-reg "datastack" context-field-offset [+] MOV
199     EAX EAX [] MOV
200     temp-reg "datastack" context-field-offset [+] bootstrap-cell SUB ;
201
202 : call-unbox-func ( func -- )
203     4 save-vm-ptr
204     0 stack@ EAX MOV
205     f %alien-invoke ;
206
207 M: x86.32 %unbox ( n rep func -- )
208     #! The value being unboxed must already be in EAX.
209     #! If n is f, we're unboxing a return value about to be
210     #! returned by the callback. Otherwise, we're unboxing
211     #! a parameter to a C function about to be called.
212     call-unbox-func
213     ! Store the return value on the C stack
214     over [ [ local@ ] dip store-return-reg ] [ 2drop ] if ;
215
216 M: x86.32 %unbox-long-long ( n func -- )
217     call-unbox-func
218     ! Store the return value on the C stack
219     [
220         [ local@ EAX MOV ]
221         [ 4 + local@ EDX MOV ] bi
222     ] when* ;
223
224 : %unbox-struct-1 ( -- )
225     #! Alien must be in EAX.
226     4 save-vm-ptr
227     0 stack@ EAX MOV
228     "alien_offset" f %alien-invoke
229     ! Load first cell
230     EAX EAX [] MOV ;
231
232 : %unbox-struct-2 ( -- )
233     #! Alien must be in EAX.
234     4 save-vm-ptr
235     0 stack@ EAX MOV
236     "alien_offset" f %alien-invoke
237     ! Load second cell
238     EDX EAX 4 [+] MOV
239     ! Load first cell
240     EAX EAX [] MOV ;
241
242 M: x86 %unbox-small-struct ( size -- )
243     #! Alien must be in EAX.
244     heap-size cell align cell /i {
245         { 1 [ %unbox-struct-1 ] }
246         { 2 [ %unbox-struct-2 ] }
247     } case ;
248
249 M:: x86.32 %unbox-large-struct ( n c-type -- )
250     ! Alien must be in EAX.
251     ! Compute destination address
252     EDX n local@ LEA
253     12 save-vm-ptr
254     8 stack@ c-type heap-size MOV
255     4 stack@ EDX MOV
256     0 stack@ EAX MOV
257     "to_value_struct" f %alien-invoke ;
258
259 M: x86.32 %prepare-alien-indirect ( -- )
260     EAX ds-reg [] MOV
261     ds-reg 4 SUB
262     4 save-vm-ptr
263     0 stack@ EAX MOV
264     "pinned_alien_offset" f %alien-invoke
265     EBP EAX MOV ;
266
267 M: x86.32 %alien-indirect ( -- )
268     EBP CALL ;
269
270 M: x86.32 %begin-callback ( -- )
271     0 save-vm-ptr
272     ESP 4 [+] 0 MOV
273     "begin_callback" f %alien-invoke ;
274
275 M: x86.32 %alien-callback ( quot -- )
276     EAX EDX %restore-context
277     EAX swap %load-reference
278     EAX quot-entry-point-offset [+] CALL
279     EAX EDX %save-context ;
280
281 M: x86.32 %end-callback ( -- )
282     0 save-vm-ptr
283     "end_callback" f %alien-invoke ;
284
285 M: x86.32 %end-callback-value ( ctype -- )
286     %pop-context-stack
287     4 stack@ EAX MOV
288     %end-callback
289     ! Place former top of data stack back in EAX
290     EAX 4 stack@ MOV
291     ! Unbox EAX
292     unbox-return ;
293
294 GENERIC: float-function-param ( stack-slot dst src -- )
295
296 M:: spill-slot float-function-param ( stack-slot dst src -- )
297     ! We can clobber dst here since its going to contain the
298     ! final result
299     dst src double-rep %copy
300     stack-slot dst double-rep %copy ;
301
302 M: register float-function-param
303     nip double-rep %copy ;
304
305 : float-function-return ( reg -- )
306     ESP [] FSTPL
307     ESP [] MOVSD
308     ESP 16 ADD ;
309
310 M:: x86.32 %unary-float-function ( dst src func -- )
311     ESP -16 [+] dst src float-function-param
312     ESP 16 SUB
313     func "libm" load-library %alien-invoke
314     dst float-function-return ;
315
316 M:: x86.32 %binary-float-function ( dst src1 src2 func -- )
317     ESP -16 [+] dst src1 float-function-param
318     ESP  -8 [+] dst src2 float-function-param
319     ESP 16 SUB
320     func "libm" load-library %alien-invoke
321     dst float-function-return ;
322
323 : funny-large-struct-return? ( params -- ? )
324     #! MINGW ABI incompatibility disaster
325     [ return>> large-struct? ]
326     [ abi>> mingw = os windows? not or ]
327     bi and ;
328
329 : stack-arg-size ( params -- n )
330     dup abi>> '[
331         alien-parameters flatten-value-types
332         [ _ alloc-parameter 2drop ] each
333         stack-params get
334     ] with-param-regs ;
335
336 M: x86.32 stack-cleanup ( params -- n )
337     #! a) Functions which are stdcall/fastcall/thiscall have to
338     #! clean up the caller's stack frame.
339     #! b) Functions returning large structs on MINGW have to
340     #! fix ESP.
341     {
342         { [ dup abi>> callee-cleanup? ] [ stack-arg-size ] }
343         { [ dup funny-large-struct-return? ] [ drop 4 ] }
344         [ drop 0 ]
345     } cond ;
346
347 M: x86.32 %cleanup ( params -- )
348     stack-cleanup [ ESP swap SUB ] unless-zero ;
349
350 M:: x86.32 %call-gc ( gc-roots -- )
351     4 save-vm-ptr
352     0 stack@ gc-roots gc-root-offsets %load-reference
353     "inline_gc" f %alien-invoke ;
354
355 M: x86.32 dummy-stack-params? f ;
356
357 M: x86.32 dummy-int-params? f ;
358
359 M: x86.32 dummy-fp-params? f ;
360
361 ! Dreadful
362 M: object flatten-value-type (flatten-stack-type) ;
363 M: struct-c-type flatten-value-type (flatten-stack-type) ;
364 M: long-long-type flatten-value-type (flatten-stack-type) ;
365 M: c-type flatten-value-type
366     dup rep>> int-rep? [ (flatten-int-type) ] [ (flatten-stack-type) ] if ;
367
368 M: x86.32 struct-return-pointer-type
369     os linux? void* (stack-value) ? ;
370
371 check-sse