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