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