0.9.10.11:
[sbcl.git] / src / runtime / x86-64-assem.S
1 /*
2  * very-low-level utilities for runtime support
3  */
4
5 /*
6  * This software is part of the SBCL system. See the README file for
7  * more information.
8  *
9  * This software is derived from the CMU CL system, which was
10  * written at Carnegie Mellon University and released into the
11  * public domain. The software is in the public domain and is
12  * provided with absolutely no warranty. See the COPYING and CREDITS
13  * files for more information.
14  */
15 \f
16 #define LANGUAGE_ASSEMBLY
17 #include "validate.h"
18 #include "sbcl.h"
19 #include "genesis/closure.h"
20 #include "genesis/fdefn.h"
21 #include "genesis/static-symbols.h"
22 #include "genesis/symbol.h"
23 #include "genesis/thread.h"
24         
25 /* Minimize conditionalization for different OS naming schemes. */
26 #if defined __linux__  || defined __FreeBSD__ /* (but *not* OpenBSD) */
27 #define GNAME(var) var
28 #else
29 #define GNAME(var) _##var
30 #endif
31
32 /* Get the right type of alignment. Linux and FreeBSD (but not OpenBSD)
33  * want alignment in bytes. */
34 #if defined(__linux__) || defined(__FreeBSD__)
35 #define align_4byte     4
36 #define align_8byte     8
37 #define align_16byte    16
38 #define align_32byte    32
39 #else
40 #define align_4byte     2
41 #define align_8byte     3
42 #define align_16byte    4       
43 #endif                  
44
45         .text
46         .global GNAME(foreign_function_call_active)
47         .global GNAME(all_threads)
48         
49 \f
50 /* From lower to higher-numbered addresses, the stack contains 
51  * return address, arg 0, arg 1, arg 2 ...
52  * rax contains the address of the function to call
53  * Lisp expects return value in rax, whic is already consistent with C
54  * XXXX correct floating point handling is unimplemented so far
55  * Based on comments cleaned from x86-assem.S, we believe that 
56  * Lisp is expecting us to preserve rsi, rdi, rsp (no idea about r8-15)
57  */
58         .text
59         .align  align_16byte,0x90
60         .global GNAME(call_into_c)
61         .type   GNAME(call_into_c),@function
62 GNAME(call_into_c):
63         /* ABI requires that the direction flag be clear on function
64          * entry and exit. */
65         cld
66         
67         push    %rbp            # Save old frame pointer.
68         mov     %rsp,%rbp       # Establish new frame.
69
70         push    %rsi            # args are going in here
71         push    %rdi
72         mov     16(%rbp),%rdi
73         mov     24(%rbp),%rsi
74         mov     32(%rbp),%rdx
75         mov     40(%rbp),%rcx
76         mov     48(%rbp),%rcx
77         mov     56(%rbp),%r8
78         mov     64(%rbp),%r9
79         call    *%rax
80         mov     %rbp,%rsp
81         pop     %rbp
82         ret
83         .size   GNAME(call_into_c), . - GNAME(call_into_c)
84
85 \f
86         .text   
87         .global GNAME(call_into_lisp_first_time)
88         .type  GNAME(call_into_lisp_first_time),@function
89                 
90 /* The *ALIEN-STACK* pointer is set up on the first call_into_lisp when
91  * the stack changes.  We don't worry too much about saving registers 
92  * here, because we never expect to return from the initial call to lisp 
93  * anyway */
94         
95         .align  align_16byte,0x90
96 GNAME(call_into_lisp_first_time):
97         push    %rbp            # Save old frame pointer.
98         mov     %rsp,%rbp       # Establish new frame.
99         mov    %rsp,ALIEN_STACK + SYMBOL_VALUE_OFFSET
100         mov    GNAME(all_threads),%rax
101         mov    THREAD_CONTROL_STACK_START_OFFSET(%rax) ,%rsp
102         /* don't think too hard about what happens if we get interrupted
103         * here */
104         add     $THREAD_CONTROL_STACK_SIZE-16,%rsp
105         jmp     Lstack
106 \f
107         .text   
108         .global GNAME(call_into_lisp)
109         .type  GNAME(call_into_lisp),@function
110                 
111 /*
112  * amd64 calling convention: C expects that
113  * arguments go in rdi rsi rdx rcx r8 r9
114  * return values in rax rdx
115  * callee saves rbp rbx r12-15 if it uses them
116  */
117         
118         .align  align_16byte,0x90
119 GNAME(call_into_lisp):
120         push    %rbp            # Save old frame pointer.
121         mov     %rsp,%rbp       # Establish new frame.
122 Lstack:
123         /* FIXME x86 saves FPU state here */
124         push    %rbx    # these regs are callee-saved according to C
125         push    %r12    # so must be preserved and restored when 
126         push    %r13    # the lisp function returns
127         push    %r14    #
128         push    %r15    #
129
130         mov     %rsp,%rbx       # remember current stack
131         push    %rbx            # Save entry stack on (maybe) new stack.
132
133         push    %rdi    # args from C
134         push    %rsi    #
135         push    %rdx    #
136 #ifdef LISP_FEATURE_SB_THREAD
137         mov     specials,%rdi
138         call    pthread_getspecific
139         mov     %rax,%r12
140 #endif
141         pop     %rcx    # num args
142         pop     %rbx    # arg vector
143         pop     %rax    # function ptr/lexenv
144
145         xor     %rdx,%rdx       # clear any descriptor registers 
146         xor     %rdi,%rdi       # that we can't be sure we'll 
147         xor     %rsi,%rsi       # initialise properly.  XX do r8-r15 too?
148         shl     $3,%rcx         # (fixnumize num-args)
149         cmp     $0,%rcx
150         je      Ldone
151         mov     0(%rbx),%rdx    # arg0
152         cmp     $8,%rcx
153         je      Ldone
154         mov     8(%rbx),%rdi    # arg1
155         cmp     $16,%rcx
156         je      Ldone
157         mov     16(%rbx),%rsi   # arg2
158 Ldone:  
159         /* Registers rax, rcx, rdx, rdi, and rsi are now live. */
160         xor     %rbx,%rbx       # available
161
162         /* Alloc new frame. */
163         mov     %rsp,%rbx       # The current sp marks start of new frame.
164         push    %rbp            # fp in save location S0
165         sub     $16,%rsp        # Ensure 3 slots are allocated, one above.
166         mov     %rbx,%rbp       # Switch to new frame.
167
168 Lcall:
169         call    *CLOSURE_FUN_OFFSET(%rax)
170         
171         /* If the function returned multiple values, it will return to
172            this point.  Lose them */
173         jnc     LsingleValue    
174         mov     %rbx, %rsp
175 LsingleValue:   
176
177 /* Restore the stack, in case there was a stack change. */
178         pop     %rsp            # c-sp
179
180 /* Restore C regs */
181         pop     %r15
182         pop     %r14
183         pop     %r13
184         pop     %r12
185         pop     %rbx
186
187         /* ABI requires that the direction flag be clear on function
188          * entry and exit. */
189         cld
190         
191 /* FIXME Restore the NPX state. */
192
193         /* return value is already in rax where lisp expects it */
194         leave
195         ret
196         .size   GNAME(call_into_lisp), . - GNAME(call_into_lisp)
197 \f
198 /* support for saving and restoring the NPX state from C */
199         .text
200         .global GNAME(fpu_save)
201         .type   GNAME(fpu_save),@function
202         .align  2,0x90
203 GNAME(fpu_save):
204         mov     4(%rsp),%rax
205         fnsave  (%rax)          # Save the NPX state. (resets NPX)
206         ret
207         .size   GNAME(fpu_save),.-GNAME(fpu_save)
208
209         .global GNAME(fpu_restore)
210         .type   GNAME(fpu_restore),@function
211         .align  2,0x90
212 GNAME(fpu_restore):
213         mov     4(%rsp),%rax
214         frstor  (%rax)          # Restore the NPX state.
215         ret
216         .size   GNAME(fpu_restore),.-GNAME(fpu_restore)
217 \f
218 /*
219  * the undefined-function trampoline
220  */
221         .text
222         .align  align_8byte,0x90
223         .global GNAME(undefined_tramp)
224         .type   GNAME(undefined_tramp),@function
225 GNAME(undefined_tramp):
226         int3
227         .byte   trap_Error
228         .byte   2
229         .byte   UNDEFINED_FUN_ERROR
230         .byte   sc_DescriptorReg # eax in the Descriptor-reg SC
231         ret
232         .size   GNAME(undefined_tramp), .-GNAME(undefined_tramp)
233
234
235         .text
236         .align  align_8byte,0x90
237         .global GNAME(alloc_tramp)
238         .type   GNAME(alloc_tramp),@function
239 GNAME(alloc_tramp):
240         push    %rbp            # Save old frame pointer.
241         mov     %rsp,%rbp       # Establish new frame.
242         push    %rax
243         push    %rcx
244         push    %rdx
245         push    %rsi
246         push    %rdi
247         push    %r8
248         push    %r9
249         push    %r10
250         push    %r11
251         mov     16(%rbp),%rdi   
252         call    alloc
253         mov     %rax,16(%rbp)
254         pop     %r11
255         pop     %r10
256         pop     %r9
257         pop     %r8
258         pop     %rdi
259         pop     %rsi
260         pop     %rdx
261         pop     %rcx
262         pop     %rax
263         pop     %rbp
264         ret
265         .size   GNAME(alloc_tramp),.-GNAME(alloc_tramp)
266
267                 
268 /*
269  * the closure trampoline
270  */
271         .text
272         .align  align_8byte,0x90
273         .global GNAME(closure_tramp)
274         .type   GNAME(closure_tramp),@function
275 GNAME(closure_tramp):
276         mov     FDEFN_FUN_OFFSET(%rax),%rax
277         /* FIXME: The '*' after "jmp" in the next line is from PVE's
278          * patch posted to the CMU CL mailing list Oct 6, 1999. It looks
279          * reasonable, and it certainly seems as though if CMU CL needs it,
280          * SBCL needs it too, but I haven't actually verified that it's
281          * right. It would be good to find a way to force the flow of
282          * control through here to test it. */
283         jmp     *CLOSURE_FUN_OFFSET(%rax)
284         .size   GNAME(closure_tramp), .-GNAME(closure_tramp)
285
286 /*
287  * fun-end breakpoint magic
288  */
289         .text
290         .global GNAME(fun_end_breakpoint_guts)
291         .align  align_8byte
292 GNAME(fun_end_breakpoint_guts):
293         /* Multiple Value return */
294         jc      multiple_value_return
295         /* Single value return: The eventual return will now use the
296            multiple values return convention but with a return values
297            count of one. */
298         mov     %rsp,%rbx       # Setup ebx - the ofp.
299         sub     $8,%rsp         # Allocate one stack slot for the return value
300         mov     $8,%rcx         # Setup ecx for one return value.
301         mov     $NIL,%rdi       # default second value
302         mov     $NIL,%rsi       # default third value
303                 
304 multiple_value_return:
305         
306         .global GNAME(fun_end_breakpoint_trap)
307 GNAME(fun_end_breakpoint_trap):
308         int3
309         .byte   trap_FunEndBreakpoint
310         hlt                     # We should never return here.
311
312         .global GNAME(fun_end_breakpoint_end)
313 GNAME(fun_end_breakpoint_end):
314
315 \f
316         .global GNAME(do_pending_interrupt)
317         .type   GNAME(do_pending_interrupt),@function
318         .align  align_8byte,0x90
319 GNAME(do_pending_interrupt):
320         int3
321         .byte   trap_PendingInterrupt
322         ret
323         .size   GNAME(do_pending_interrupt),.-GNAME(do_pending_interrupt)
324 \f
325         .globl  GNAME(post_signal_tramp)
326         .type   GNAME(post_signal_tramp),@function
327         .align  align_8byte,0x90
328 GNAME(post_signal_tramp):
329         /* this is notionally the second half of a function whose first half
330          * doesn't exist.  This is where call_into_lisp returns when called 
331          * using return_to_lisp_function */
332         popq %r15
333         popq %r14
334         popq %r13
335         popq %r12
336         popq %r11
337         popq %r10
338         popq %r9
339         popq %r8
340         popq %rdi
341         popq %rsi
342         /* skip RBP and RSP */
343         popq %rbx
344         popq %rdx
345         popq %rcx
346         popq %rax
347         popfq
348         leave
349         ret
350         .size GNAME(post_signal_tramp),.-GNAME(post_signal_tramp)
351 \f
352         .text
353         .align  align_8byte,0x90
354         .global GNAME(fast_bzero)
355         .type   GNAME(fast_bzero),@function
356         
357 GNAME(fast_bzero):
358         /* A fast routine for zero-filling blocks of memory that are
359          * guaranteed to start and end at a 4096-byte aligned address.
360          */
361         shr $6, %rsi              /* Amount of 64-byte blocks to copy */
362         jz Lend                   /* If none, stop */
363         mov %rsi, %rcx            /* Save start address */
364         movups %xmm7, -16(%rsp)   /* Save XMM register */
365         xorps  %xmm7, %xmm7       /* Zero the XMM register */
366         jmp Lloop
367         .align 16                 
368 Lloop:
369
370         /* Copy the 16 zeroes from xmm7 to memory, 4 times. MOVNTDQ is the
371          * non-caching double-quadword moving variant, i.e. the memory areas
372          * we're touching are not fetched into the L1 cache, since we're just
373          * going to overwrite the memory soon anyway.
374          */
375         movntdq %xmm7, 0(%rdi)
376         movntdq %xmm7, 16(%rdi)
377         movntdq %xmm7, 32(%rdi)
378         movntdq %xmm7, 48(%rdi)
379
380         add $64, %rdi  /* Advance pointer */
381         dec %rsi       /* Decrement 64-byte block count */
382         jnz Lloop
383         mfence         /* Ensure that the writes are globally visible, since
384                         * MOVNTDQ is weakly ordered */
385         movups -16(%rsp), %xmm7 /* Restore the XMM register */
386         prefetcht0 0(%rcx)      /* Prefetch the start of the block into cache,
387                                  * since it's likely to be used immediately. */
388 Lend:        
389         ret
390         .size   GNAME(fast_bzero), .-GNAME(fast_bzero)
391
392         .end