1.0.9.62: Performance and stability improvement of threading on FreeBSD
[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 "genesis/config.h"
18 #include "validate.h"
19 #include "sbcl.h"
20 #include "genesis/closure.h"
21 #include "genesis/funcallable-instance.h"
22 #include "genesis/fdefn.h"
23 #include "genesis/static-symbols.h"
24 #include "genesis/symbol.h"
25 #include "genesis/thread.h"
26         
27 /* Minimize conditionalization for different OS naming schemes. */
28 #if defined __linux__  || defined __FreeBSD__ /* (but *not* OpenBSD) */
29 #define GNAME(var) var
30 #else
31 #define GNAME(var) _##var
32 #endif
33
34 /* Get the right type of alignment. Linux and FreeBSD (but not OpenBSD)
35  * want alignment in bytes. */
36 #if defined(__linux__) || defined(__FreeBSD__)
37 #define align_4byte     4
38 #define align_8byte     8
39 #define align_16byte    16
40 #define align_32byte    32
41 #else
42 #define align_4byte     2
43 #define align_8byte     3
44 #define align_16byte    4       
45 #endif                  
46
47 /*
48  * The assembler used for win32 doesn't like .type or .size directives,
49  * so we want to conditionally kill them out. So let's wrap them in macros
50  * that are defined to be no-ops on win32. Hopefully this still works on
51  * other platforms.
52  */
53 #if !defined(LISP_FEATURE_WIN32) && !defined(LISP_FEATURE_DARWIN)
54 #define TYPE(name) .type name,@function
55 #define SIZE(name) .size name,.-name
56 #define DOLLAR(name) $(name)
57 #else
58 #define TYPE(name)
59 #define SIZE(name)
60 #endif
61
62 /*
63  * x86/darwin (as of MacOS X 10.4.5) doesn't reliably fire signal
64  * handlers (SIGTRAP or Mach exception handlers) for 0xCC, wo we have
65  * to use ud2 instead. ud2 is an undefined opcode, #x0b0f, or
66  * 0F 0B in low-endian notation, that causes SIGILL to fire. We check
67  * for this instruction in the SIGILL handler and if we see it, we
68  * advance the EIP by two bytes to skip over ud2 instruction and
69  * call sigtrap_handler. */
70 #if defined(LISP_FEATURE_DARWIN)
71 #define TRAP ud2
72 #else
73 #define TRAP int3
74 #endif
75
76 /*
77  * More Apple assembler hacks
78  */
79
80 #if defined(LISP_FEATURE_DARWIN)
81 /* global symbol x86-64 sym(%rip) hack:*/
82 #define GSYM(name) name(%rip)
83 #define END()
84 #else
85 #define GSYM(name) $name
86 #define END() .end
87 #endif
88
89         
90         .text
91         .globl  GNAME(all_threads)
92         
93         
94 \f
95 /* From lower to higher-numbered addresses, the stack contains 
96  * return address, arg 0, arg 1, arg 2 ...
97  * rax contains the address of the function to call
98  * Lisp expects return value in rax, whic is already consistent with C
99  * XXXX correct floating point handling is unimplemented so far
100  * Based on comments cleaned from x86-assem.S, we believe that 
101  * Lisp is expecting us to preserve rsi, rdi, rsp (no idea about r8-15)
102  */
103         .text
104         .align  align_16byte,0x90
105         .globl  GNAME(call_into_c)
106         TYPE(GNAME(call_into_c))
107 GNAME(call_into_c):
108         /* ABI requires that the direction flag be clear on function
109          * entry and exit. */
110         cld
111         push    %rbp            # Save old frame pointer.
112         mov     %rsp,%rbp       # Establish new frame.
113
114         push    %rsi            # args are going in here
115         push    %rdi
116         mov     16(%rbp),%rdi
117         mov     24(%rbp),%rsi
118         mov     32(%rbp),%rdx
119         mov     40(%rbp),%rcx
120         mov     48(%rbp),%rcx
121         mov     56(%rbp),%r8
122         mov     64(%rbp),%r9
123         call    *%rax
124         mov     %rbp,%rsp
125         pop     %rbp
126         ret
127         SIZE(GNAME(call_into_c))
128
129 \f
130         .text   
131         .globl  GNAME(call_into_lisp_first_time)
132         TYPE(GNAME(call_into_lisp_first_time))
133                 
134 /* The *ALIEN-STACK* pointer is set up on the first call_into_lisp when
135  * the stack changes.  We don't worry too much about saving registers 
136  * here, because we never expect to return from the initial call to lisp 
137  * anyway */
138         
139         .align  align_16byte,0x90
140 GNAME(call_into_lisp_first_time):
141         push    %rbp            # Save old frame pointer.
142         mov     %rsp,%rbp       # Establish new frame.
143         mov     %rsp,ALIEN_STACK + SYMBOL_VALUE_OFFSET
144 #if defined(LISP_FEATURE_DARWIN)
145         movq    GSYM(GNAME(all_threads)),%rax
146 #else
147         movq    GNAME(all_threads),%rax
148 #endif
149         mov     THREAD_CONTROL_STACK_START_OFFSET(%rax) ,%rsp
150         /* don't think too hard about what happens if we get interrupted
151         * here */
152         add     $(THREAD_CONTROL_STACK_SIZE)-16,%rsp
153         jmp     Lstack
154 \f
155         .text   
156         .globl  GNAME(call_into_lisp)
157         TYPE(GNAME(call_into_lisp))
158                 
159 /*
160  * amd64 calling convention: C expects that
161  * arguments go in rdi rsi rdx rcx r8 r9
162  * return values in rax rdx
163  * callee saves rbp rbx r12-15 if it uses them
164  */
165         
166         .align  align_16byte,0x90
167 GNAME(call_into_lisp):
168         push    %rbp            # Save old frame pointer.
169         mov     %rsp,%rbp       # Establish new frame.
170 Lstack:
171         /* FIXME x86 saves FPU state here */
172         push    %rbx    # these regs are callee-saved according to C
173         push    %r12    # so must be preserved and restored when 
174         push    %r13    # the lisp function returns
175         push    %r14    #
176         push    %r15    #
177
178         mov     %rsp,%rbx       # remember current stack
179         push    %rbx            # Save entry stack on (maybe) new stack.
180
181         push    %rdi    # args from C
182         push    %rsi    #
183         push    %rdx    #
184 #ifdef LISP_FEATURE_SB_THREAD
185 #ifdef LISP_FEATURE_GCC_TLS
186         movq    %fs:0, %rax
187         movq    GNAME(current_thread)@TPOFF(%rax), %r12
188 #else
189 #ifdef LISP_FEATURE_DARWIN
190         mov     GSYM(GNAME(specials)),%rdi
191 #else
192         mov     specials,%rdi
193 #endif
194         call    GNAME(pthread_getspecific)
195         mov     %rax,%r12
196 #endif
197 #endif
198         pop     %rcx    # num args
199         pop     %rbx    # arg vector
200         pop     %rax    # function ptr/lexenv
201
202         xor     %rdx,%rdx       # clear any descriptor registers 
203         xor     %rdi,%rdi       # that we can't be sure we'll 
204         xor     %rsi,%rsi       # initialise properly.  XX do r8-r15 too?
205         shl     $3,%rcx         # (fixnumize num-args)
206         cmp     $0,%rcx
207         je      Ldone
208         mov     0(%rbx),%rdx    # arg0
209         cmp     $8,%rcx
210         je      Ldone
211         mov     8(%rbx),%rdi    # arg1
212         cmp     $16,%rcx
213         je      Ldone
214         mov     16(%rbx),%rsi   # arg2
215 Ldone:  
216         /* Registers rax, rcx, rdx, rdi, and rsi are now live. */
217         xor     %rbx,%rbx       # available
218
219         /* Alloc new frame. */
220         mov     %rsp,%rbx       # The current sp marks start of new frame.
221         push    %rbp            # fp in save location S0
222         sub     $16,%rsp        # Ensure 3 slots are allocated, one above.
223         mov     %rbx,%rbp       # Switch to new frame.
224
225 Lcall:
226         call    *CLOSURE_FUN_OFFSET(%rax)
227         
228         /* If the function returned multiple values, it will return to
229            this point.  Lose them */
230         jnc     LsingleValue    
231         mov     %rbx, %rsp
232 LsingleValue:   
233
234 /* Restore the stack, in case there was a stack change. */
235         pop     %rsp            # c-sp
236
237 /* Restore C regs */
238         pop     %r15
239         pop     %r14
240         pop     %r13
241         pop     %r12
242         pop     %rbx
243
244         /* ABI requires that the direction flag be clear on function
245          * entry and exit. */
246         cld
247         
248 /* FIXME Restore the NPX state. */
249
250         /* return value is already in rax where lisp expects it */
251         leave
252         ret
253         SIZE(GNAME(call_into_lisp))
254 \f
255 /* support for saving and restoring the NPX state from C */
256         .text
257         .globl  GNAME(fpu_save)
258         TYPE(GNAME(fpu_save))
259         .align  2,0x90
260 GNAME(fpu_save):
261         mov     4(%rsp),%rax
262         fnsave  (%rax)          # Save the NPX state. (resets NPX)
263         ret
264         SIZE(GNAME(fpu_save))
265
266         .globl  GNAME(fpu_restore)
267         TYPE(GNAME(fpu_restore))
268         .align  2,0x90
269 GNAME(fpu_restore):
270         mov     4(%rsp),%rax
271         frstor  (%rax)          # Restore the NPX state.
272         ret
273         SIZE(GNAME(fpu_restore))
274 \f
275 /*
276  * the undefined-function trampoline
277  */
278         .text
279         .align  align_16byte,0x90
280         .globl  GNAME(undefined_tramp)
281         TYPE(GNAME(undefined_tramp))
282 GNAME(undefined_tramp):
283         TRAP
284         .byte   trap_Error
285         .byte   2
286         .byte   UNDEFINED_FUN_ERROR
287         .byte   sc_DescriptorReg # eax in the Descriptor-reg SC
288         ret
289         SIZE(GNAME(undefined_tramp))
290
291
292         .text
293         .align  align_16byte,0x90
294         .globl  GNAME(alloc_tramp)
295         TYPE(GNAME(alloc_tramp))
296 GNAME(alloc_tramp):
297         push    %rbp            # Save old frame pointer.
298         mov     %rsp,%rbp       # Establish new frame.
299         push    %rax
300         push    %rcx
301         push    %rdx
302         push    %rsi
303         push    %rdi
304         push    %r8
305         push    %r9
306         push    %r10
307         push    %r11
308         mov     16(%rbp),%rdi   
309         call    GNAME(alloc)
310         mov     %rax,16(%rbp)
311         pop     %r11
312         pop     %r10
313         pop     %r9
314         pop     %r8
315         pop     %rdi
316         pop     %rsi
317         pop     %rdx
318         pop     %rcx
319         pop     %rax
320         pop     %rbp
321         ret
322         SIZE(GNAME(alloc_tramp))
323
324                 
325 /*
326  * the closure trampoline
327  */
328         .text
329         .align  align_16byte,0x90
330         .globl  GNAME(closure_tramp)
331         TYPE(GNAME(closure_tramp))
332 GNAME(closure_tramp):
333         mov     FDEFN_FUN_OFFSET(%rax),%rax
334         /* FIXME: The '*' after "jmp" in the next line is from PVE's
335          * patch posted to the CMU CL mailing list Oct 6, 1999. It looks
336          * reasonable, and it certainly seems as though if CMU CL needs it,
337          * SBCL needs it too, but I haven't actually verified that it's
338          * right. It would be good to find a way to force the flow of
339          * control through here to test it. */
340         jmp     *CLOSURE_FUN_OFFSET(%rax)
341         SIZE(GNAME(closure_tramp))
342
343         .text
344         .align  align_16byte,0x90
345         .globl  GNAME(funcallable_instance_tramp)
346 #if !defined(LISP_FEATURE_DARWIN)
347         .type   GNAME(funcallable_instance_tramp),@function
348 #endif
349         GNAME(funcallable_instance_tramp):
350         mov     FUNCALLABLE_INSTANCE_FUNCTION_OFFSET(%rax),%rax
351         /* KLUDGE: on this platform, whatever kind of function is in %rax
352          * now, the first word of it contains the address to jump to. */
353         jmp     *CLOSURE_FUN_OFFSET(%rax)
354 #if !defined(LISP_FEATURE_DARWIN)
355         .size   GNAME(funcallable_instance_tramp), .-GNAME(funcallable_instance_tramp)
356 #endif
357 /*
358  * fun-end breakpoint magic
359  */
360         .text
361         .globl  GNAME(fun_end_breakpoint_guts)
362         .align  align_16byte
363 GNAME(fun_end_breakpoint_guts):
364         /* Multiple Value return */
365         jc      multiple_value_return
366         /* Single value return: The eventual return will now use the
367            multiple values return convention but with a return values
368            count of one. */
369         mov     %rsp,%rbx       # Setup ebx - the ofp.
370         sub     $8,%rsp         # Allocate one stack slot for the return value
371         mov     $8,%rcx         # Setup ecx for one return value.
372 #if defined(LISP_FEATURE_DARWIN)
373         mov     GSYM(NIL),%rdi  # default second value
374         mov     GSYM(NIL),%rsi  # default third value
375 #else
376         mov     $NIL,%rdi       # default second value
377         mov     $NIL,%rsi       # default third value
378 #endif
379 multiple_value_return:
380         
381         .globl  GNAME(fun_end_breakpoint_trap)
382 GNAME(fun_end_breakpoint_trap):
383         TRAP
384         .byte   trap_FunEndBreakpoint
385         hlt                     # We should never return here.
386
387         .globl  GNAME(fun_end_breakpoint_end)
388 GNAME(fun_end_breakpoint_end):
389
390 \f
391         .globl  GNAME(do_pending_interrupt)
392         TYPE(GNAME(do_pending_interrupt))
393         .align  align_16byte,0x90
394 GNAME(do_pending_interrupt):
395         TRAP
396         .byte   trap_PendingInterrupt
397         ret
398         SIZE(GNAME(do_pending_interrupt))
399 \f
400         .globl  GNAME(post_signal_tramp)
401         TYPE(GNAME(post_signal_tramp))
402         .align  align_16byte,0x90
403 GNAME(post_signal_tramp):
404         /* this is notionally the second half of a function whose first half
405          * doesn't exist.  This is where call_into_lisp returns when called 
406          * using return_to_lisp_function */
407         popq %r15
408         popq %r14
409         popq %r13
410         popq %r12
411         popq %r11
412         popq %r10
413         popq %r9
414         popq %r8
415         popq %rdi
416         popq %rsi
417         /* skip RBP and RSP */
418         popq %rbx
419         popq %rdx
420         popq %rcx
421         popq %rax
422         popfq
423         leave
424         ret
425         SIZE(GNAME(post_signal_tramp))
426 \f
427         .text
428         .align  align_16byte,0x90
429         .globl  GNAME(fast_bzero)
430         TYPE(GNAME(fast_bzero))
431         
432 GNAME(fast_bzero):
433         /* A fast routine for zero-filling blocks of memory that are
434          * guaranteed to start and end at a 4096-byte aligned address.
435          */
436         shr $6, %rsi              /* Amount of 64-byte blocks to copy */
437         jz Lend                   /* If none, stop */
438         mov %rsi, %rcx            /* Save start address */
439         movups %xmm7, -16(%rsp)   /* Save XMM register */
440         xorps  %xmm7, %xmm7       /* Zero the XMM register */
441         jmp Lloop
442         .align align_16byte                 
443 Lloop:
444
445         /* Copy the 16 zeroes from xmm7 to memory, 4 times. MOVNTDQ is the
446          * non-caching double-quadword moving variant, i.e. the memory areas
447          * we're touching are not fetched into the L1 cache, since we're just
448          * going to overwrite the memory soon anyway.
449          */
450         movntdq %xmm7, 0(%rdi)
451         movntdq %xmm7, 16(%rdi)
452         movntdq %xmm7, 32(%rdi)
453         movntdq %xmm7, 48(%rdi)
454
455         add $64, %rdi  /* Advance pointer */
456         dec %rsi       /* Decrement 64-byte block count */
457         jnz Lloop
458         mfence         /* Ensure that the writes are globally visible, since
459                         * MOVNTDQ is weakly ordered */
460         movups -16(%rsp), %xmm7 /* Restore the XMM register */
461         prefetcht0 0(%rcx)      /* Prefetch the start of the block into cache,
462                                  * since it's likely to be used immediately. */
463 Lend:        
464         ret
465         SIZE(GNAME(fast_bzero))
466
467         END()