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