6b1f760647c307d9f24c2505ee291010d42b917e
[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__ || defined __OpenBSD__ || defined __NetBSD__ || defined __sun
29 #define GNAME(var) var
30 #else
31 #define GNAME(var) _##var
32 #endif
33
34 /* Get the right type of alignment. Linux, FreeBSD and OpenBSD
35  * want alignment in bytes. */
36 #if defined(__linux__) || defined(__FreeBSD__) || defined(__OpenBSD__) || defined __NetBSD__ || defined(__sun)
37 #define align_4byte     4
38 #define align_8byte     8
39 #define align_16byte    16
40 #define align_32byte    32
41 #define align_page      32768
42 #else
43 #define align_4byte     2
44 #define align_8byte     3
45 #define align_16byte    4       
46 #define align_page      15
47 #endif                  
48
49 /*
50  * The assembler used for win32 doesn't like .type or .size directives,
51  * so we want to conditionally kill them out. So let's wrap them in macros
52  * that are defined to be no-ops on win32. Hopefully this still works on
53  * other platforms.
54  */
55 #if !defined(LISP_FEATURE_WIN32) && !defined(LISP_FEATURE_DARWIN)
56 #define TYPE(name) .type name,@function
57 #define SIZE(name) .size name,.-name
58 #define DOLLAR(name) $(name)
59 #else
60 #define TYPE(name)
61 #define SIZE(name)
62 #endif
63
64 /*
65  * x86/darwin (as of MacOS X 10.4.5) doesn't reliably fire signal
66  * handlers (SIGTRAP or Mach exception handlers) for 0xCC, wo we have
67  * to use ud2 instead. ud2 is an undefined opcode, #x0b0f, or
68  * 0F 0B in low-endian notation, that causes SIGILL to fire. We check
69  * for this instruction in the SIGILL handler and if we see it, we
70  * advance the EIP by two bytes to skip over ud2 instruction and
71  * call sigtrap_handler. */
72 #if defined(LISP_FEATURE_UD2_BREAKPOINTS)
73 #define TRAP ud2
74 #else
75 #define TRAP int3
76 #endif
77
78 /*
79  * More Apple assembler hacks
80  */
81
82 #if defined(LISP_FEATURE_DARWIN)
83 /* global symbol x86-64 sym(%rip) hack:*/
84 #define GSYM(name) name(%rip)
85 #define END()
86 #else
87 #define GSYM(name) $name
88 #define END() .end
89 #endif
90
91         
92         .text
93         .globl  GNAME(all_threads)
94         
95         
96 \f
97 /* From lower to higher-numbered addresses, the stack contains 
98  * return address, arg 0, arg 1, arg 2 ...
99  * rax contains the address of the function to call
100  * Lisp expects return value in rax, whic is already consistent with C
101  * XXXX correct floating point handling is unimplemented so far
102  * Based on comments cleaned from x86-assem.S, we believe that 
103  * Lisp is expecting us to preserve rsi, rdi, rsp (no idea about r8-15)
104  */
105         .text
106         .align  align_16byte,0x90
107         .globl  GNAME(call_into_c)
108         TYPE(GNAME(call_into_c))
109 GNAME(call_into_c):
110         push    %rbp            # Save old frame pointer.
111         mov     %rsp,%rbp       # Establish new frame.
112
113         push    %rsi            # args are going in here
114         push    %rdi
115         mov     16(%rbp),%rdi
116         mov     24(%rbp),%rsi
117         mov     32(%rbp),%rdx
118         mov     40(%rbp),%rcx
119         mov     48(%rbp),%rcx
120         mov     56(%rbp),%r8
121         mov     64(%rbp),%r9
122         call    *%rax
123         mov     %rbp,%rsp
124         pop     %rbp
125         ret
126         SIZE(GNAME(call_into_c))
127
128 \f
129         .text   
130         .globl  GNAME(call_into_lisp_first_time)
131         TYPE(GNAME(call_into_lisp_first_time))
132                 
133 /* We don't worry too much about saving registers 
134  * here, because we never expect to return from the initial call to lisp 
135  * anyway */
136         
137         .align  align_16byte,0x90
138 GNAME(call_into_lisp_first_time):
139         push    %rbp            # Save old frame pointer.
140         mov     %rsp,%rbp       # Establish new frame.
141 #if defined(LISP_FEATURE_DARWIN)
142         movq    GSYM(GNAME(all_threads)),%rax
143 #else
144         movq    GNAME(all_threads),%rax
145 #endif
146         mov     THREAD_CONTROL_STACK_END_OFFSET(%rax) ,%rsp
147         jmp     Lstack
148 \f
149         .text   
150         .globl  GNAME(call_into_lisp)
151         TYPE(GNAME(call_into_lisp))
152                 
153 /*
154  * amd64 calling convention: C expects that
155  * arguments go in rdi rsi rdx rcx r8 r9
156  * return values in rax rdx
157  * callee saves rbp rbx r12-15 if it uses them
158  */
159         
160         .align  align_16byte,0x90
161 GNAME(call_into_lisp):
162         push    %rbp            # Save old frame pointer.
163         mov     %rsp,%rbp       # Establish new frame.
164 Lstack:
165         /* FIXME x86 saves FPU state here */
166         push    %rbx    # these regs are callee-saved according to C
167         push    %r12    # so must be preserved and restored when 
168         push    %r13    # the lisp function returns
169         push    %r14    #
170         push    %r15    #
171
172         mov     %rsp,%rbx       # remember current stack
173         push    %rbx            # Save entry stack on (maybe) new stack.
174
175         push    %rdi    # args from C
176         push    %rsi    #
177         push    %rdx    #
178 #ifdef LISP_FEATURE_SB_THREAD
179 #ifdef LISP_FEATURE_GCC_TLS
180         movq    %fs:0, %rax
181         movq    GNAME(current_thread)@TPOFF(%rax), %r12
182 #else
183 #ifdef LISP_FEATURE_DARWIN
184         mov     GSYM(GNAME(specials)),%rdi
185 #else
186         mov     specials,%rdi
187 #endif
188         call    GNAME(pthread_getspecific)
189         mov     %rax,%r12
190 #endif
191 #endif
192         pop     %rcx    # num args
193         pop     %rbx    # arg vector
194         pop     %rax    # function ptr/lexenv
195
196         xor     %rdx,%rdx       # clear any descriptor registers 
197         xor     %rdi,%rdi       # that we can't be sure we'll 
198         xor     %rsi,%rsi       # initialise properly.  XX do r8-r15 too?
199         shl     $(N_FIXNUM_TAG_BITS),%rcx       # (fixnumize num-args)
200         cmp     $0,%rcx
201         je      Ldone
202         mov     0(%rbx),%rdx    # arg0
203         cmp     $8,%rcx
204         je      Ldone
205         mov     8(%rbx),%rdi    # arg1
206         cmp     $16,%rcx
207         je      Ldone
208         mov     16(%rbx),%rsi   # arg2
209 Ldone:  
210         /* Registers rax, rcx, rdx, rdi, and rsi are now live. */
211         xor     %rbx,%rbx       # available
212
213         /* Alloc new frame. */
214         push    %rbp            # Dummy for return address
215         push    %rbp            # fp in save location S1
216         mov     %rsp,%rbp       # The current sp marks start of new frame.
217         sub     $8,%rsp         # Ensure 3 slots are allocated, two above.
218
219 Lcall:
220         call    *CLOSURE_FUN_OFFSET(%rax)
221         
222         /* If the function returned multiple values, it will return to
223            this point.  Lose them */
224         jnc     LsingleValue    
225         mov     %rbx, %rsp
226 LsingleValue:   
227
228 /* Restore the stack, in case there was a stack change. */
229         pop     %rsp            # c-sp
230
231 /* Restore C regs */
232         pop     %r15
233         pop     %r14
234         pop     %r13
235         pop     %r12
236         pop     %rbx
237
238 /* FIXME Restore the NPX state. */
239
240         mov     %rdx,%rax       # c-val
241         leave
242         ret
243         SIZE(GNAME(call_into_lisp))
244 \f
245 /* support for saving and restoring the NPX state from C */
246         .text
247         .globl  GNAME(fpu_save)
248         TYPE(GNAME(fpu_save))
249         .align  align_16byte,0x90
250 GNAME(fpu_save):
251         fnsave  (%rdi)          # Save the NPX state. (resets NPX)
252         ret
253         SIZE(GNAME(fpu_save))
254
255         .globl  GNAME(fpu_restore)
256         TYPE(GNAME(fpu_restore))
257         .align  align_16byte,0x90
258 GNAME(fpu_restore):
259         frstor  (%rdi)          # Restore the NPX state.
260         ret
261         SIZE(GNAME(fpu_restore))
262 \f
263 /*
264  * the undefined-function trampoline
265  */
266         .text
267         .align  align_16byte,0x90
268         .globl  GNAME(undefined_tramp)
269         TYPE(GNAME(undefined_tramp))
270 GNAME(undefined_tramp):
271         pop     8(%rbp)         # Save return PC for backtrace.
272         TRAP
273         .byte   trap_Error
274         .byte   2
275         .byte   UNDEFINED_FUN_ERROR
276         .byte   sc_DescriptorReg # eax in the Descriptor-reg SC
277         ret
278         SIZE(GNAME(undefined_tramp))
279
280 /* KLUDGE: FIND-ESCAPED-FRAME (SYS:SRC;CODE;DEBUG-INT.LISP) needs
281  * to know the name of the function immediately following the
282  * undefined-function trampoline. */
283
284 /* Our call-site does not take care of caller-saved xmm registers, so it
285  * falls to us spill them beforing hopping into C.
286  *
287  * We simply save all of them.
288  *
289  * (But for the sake of completeness, here is my understanding of the specs:)
290  *                     System V       Microsoft
291  * argument passing    xmm0-7         xmm0-3
292  * caller-saved        xmm8-15        xmm4-5
293  * callee-saved        -              xmm6-15
294  *
295  *  --DFL */
296
297 #define stkxmmsave(n) movaps %xmm##n, n*16(%rsp)
298 #define stkxmmload(n) movaps n*16(%rsp), %xmm##n
299 #define map_all_xmm(op) \
300         op(0);op(1);op(2);op(3);op(4);op(5);op(6);op(7); \
301     op(8);op(9);op(10);op(11);op(12);op(13);op(14);op(15);
302
303         .text
304         .align  align_16byte,0x90
305         .globl  GNAME(alloc_tramp)
306         TYPE(GNAME(alloc_tramp))
307 GNAME(alloc_tramp):
308         cld
309         push    %rbp            # Save old frame pointer.
310         mov     %rsp,%rbp       # Establish new frame.
311         and     $-32,%rsp
312         sub     $16*16,%rsp
313         map_all_xmm(stkxmmsave)
314         push    %rax
315         push    %rcx
316         push    %rdx
317         push    %rsi
318         push    %rdi
319         push    %r8
320         push    %r9
321         push    %r10
322         push    %r11
323         push    %r11
324         mov     16(%rbp),%rdi
325         call    GNAME(alloc)
326         mov     %rax,16(%rbp)
327         pop     %r11
328         pop     %r11
329         pop     %r10
330         pop     %r9
331         pop     %r8
332         pop     %rdi
333         pop     %rsi
334         pop     %rdx
335         pop     %rcx
336         pop     %rax
337         map_all_xmm(stkxmmload)
338         mov     %rbp,%rsp
339         pop     %rbp
340         ret
341         SIZE(GNAME(alloc_tramp))
342
343                 
344 /*
345  * the closure trampoline
346  */
347         .text
348         .align  align_16byte,0x90
349         .globl  GNAME(closure_tramp)
350         TYPE(GNAME(closure_tramp))
351 GNAME(closure_tramp):
352         mov     FDEFN_FUN_OFFSET(%rax),%rax
353         /* FIXME: The '*' after "jmp" in the next line is from PVE's
354          * patch posted to the CMU CL mailing list Oct 6, 1999. It looks
355          * reasonable, and it certainly seems as though if CMU CL needs it,
356          * SBCL needs it too, but I haven't actually verified that it's
357          * right. It would be good to find a way to force the flow of
358          * control through here to test it. */
359         jmp     *CLOSURE_FUN_OFFSET(%rax)
360         SIZE(GNAME(closure_tramp))
361
362         .text
363         .align  align_16byte,0x90
364         .globl  GNAME(funcallable_instance_tramp)
365 #if !defined(LISP_FEATURE_DARWIN)
366         .type   GNAME(funcallable_instance_tramp),@function
367 #endif
368         GNAME(funcallable_instance_tramp):
369         mov     FUNCALLABLE_INSTANCE_FUNCTION_OFFSET(%rax),%rax
370         /* KLUDGE: on this platform, whatever kind of function is in %rax
371          * now, the first word of it contains the address to jump to. */
372         jmp     *CLOSURE_FUN_OFFSET(%rax)
373 #if !defined(LISP_FEATURE_DARWIN)
374         .size   GNAME(funcallable_instance_tramp), .-GNAME(funcallable_instance_tramp)
375 #endif
376 /*
377  * fun-end breakpoint magic
378  */
379
380 /*
381  * For an explanation of the magic involved in function-end
382  * breakpoints, see the implementation in ppc-assem.S.
383  */
384
385         .text
386         .globl  GNAME(fun_end_breakpoint_guts)
387         .align  align_16byte
388 GNAME(fun_end_breakpoint_guts):
389         /* Multiple Value return */
390         jc      multiple_value_return
391         /* Single value return: The eventual return will now use the
392            multiple values return convention but with a return values
393            count of one. */
394         mov     %rsp,%rbx       # Setup ebx - the ofp.
395         sub     $8,%rsp         # Allocate one stack slot for the return value
396         mov     $8,%rcx         # Setup ecx for one return value.
397 #if defined(LISP_FEATURE_DARWIN)
398         mov     GSYM(NIL),%rdi  # default second value
399         mov     GSYM(NIL),%rsi  # default third value
400 #else
401         mov     $NIL,%rdi       # default second value
402         mov     $NIL,%rsi       # default third value
403 #endif
404 multiple_value_return:
405         
406         .globl  GNAME(fun_end_breakpoint_trap)
407         .align  align_16byte,0x90
408 GNAME(fun_end_breakpoint_trap):
409         TRAP
410         .byte   trap_FunEndBreakpoint
411         hlt                     # We should never return here.
412
413         .globl  GNAME(fun_end_breakpoint_end)
414 GNAME(fun_end_breakpoint_end):
415
416 \f
417         .globl  GNAME(do_pending_interrupt)
418         TYPE(GNAME(do_pending_interrupt))
419         .align  align_16byte,0x90
420 GNAME(do_pending_interrupt):
421         TRAP
422         .byte   trap_PendingInterrupt
423         ret
424         SIZE(GNAME(do_pending_interrupt))
425 \f
426         .globl  GNAME(post_signal_tramp)
427         TYPE(GNAME(post_signal_tramp))
428         .align  align_16byte,0x90
429 GNAME(post_signal_tramp):
430         /* this is notionally the second half of a function whose first half
431          * doesn't exist.  This is where call_into_lisp returns when called 
432          * using return_to_lisp_function */
433         popq %r15
434         popq %r14
435         popq %r13
436         popq %r12
437         popq %r11
438         popq %r10
439         popq %r9
440         popq %r8
441         popq %rdi
442         popq %rsi
443         /* skip RBP and RSP */
444         popq %rbx
445         popq %rdx
446         popq %rcx
447         popq %rax
448         popfq
449         leave
450         ret
451         SIZE(GNAME(post_signal_tramp))
452 \f
453         .text
454         .align  align_16byte,0x90
455         .globl  GNAME(fast_bzero)
456         TYPE(GNAME(fast_bzero))
457
458         #ifdef LISP_FEATURE_WIN32
459         #define xmmreg xmm7
460         #define redsave(reg,off) movups reg,-off(%rsp)
461         #define redrestore(reg,off) movups -off(%rsp),reg
462         #else
463         #define xmmreg xmm0
464         #define redsave(reg,off)
465         #define redrestore(reg,off)
466         #endif
467
468 GNAME(fast_bzero):
469         /* A fast routine for zero-filling blocks of memory that are
470          * guaranteed to start and end at a 4096-byte aligned address.
471          */
472         shr $6, %rsi              /* Amount of 64-byte blocks to copy */
473         jz Lend                   /* If none, stop */
474         mov %rsi, %rcx            /* Save start address */
475         redsave(%xmmreg,16)
476         xorps  %xmmreg, %xmmreg       /* Zero the XMM register */
477         jmp Lloop
478         .align align_16byte
479 Lloop:
480
481         /* Copy the 16 zeroes from xmm7 to memory, 4 times. MOVNTDQ is the
482          * non-caching double-quadword moving variant, i.e. the memory areas
483          * we're touching are not fetched into the L1 cache, since we're just
484          * going to overwrite the memory soon anyway.
485          */
486         movntdq %xmmreg, 0(%rdi)
487         movntdq %xmmreg, 16(%rdi)
488         movntdq %xmmreg, 32(%rdi)
489         movntdq %xmmreg, 48(%rdi)
490
491         add $64, %rdi  /* Advance pointer */
492         dec %rsi       /* Decrement 64-byte block count */
493         jnz Lloop
494         mfence         /* Ensure that the writes are globally visible, since
495                         * MOVNTDQ is weakly ordered */
496         redrestore(%xmmreg,16)
497         prefetcht0 0(%rcx)      /* Prefetch the start of the block into cache,
498                                  * since it's likely to be used immediately. */
499 Lend:        
500         ret
501         SIZE(GNAME(fast_bzero))
502
503 \f
504 /* When LISP_FEATURE_C_STACK_IS_CONTROL_STACK, we cannot safely scrub
505  * the control stack from C, largely due to not knowing where the
506  * active stack frame ends.  On such platforms, we reimplement the
507  * core scrubbing logic in assembly, in this case here:
508  */
509         .text
510         .align  align_16byte,0x90
511         .globl GNAME(arch_scrub_control_stack)
512         TYPE(GNAME(arch_scrub_control_stack))
513 GNAME(arch_scrub_control_stack):
514         /* We are passed three parameters:
515          * A (struct thread *) in RDI,
516          * the address of the guard page in RSI, and
517          * the address of the hard guard page in RDX.
518          * We may trash RAX, RCX, and R8-R11 with impunity.
519          * [RSP] is our return address, [RSP-8] is the first
520          * stack slot to scrub. */
521
522         /* We start by setting up our scrub pointer in RAX, our
523          * guard page upper bound in R8, and our hard guard
524          * page upper bound in R9. */
525         lea     -8(%rsp), %rax
526 #ifdef LISP_FEATURE_DARWIN
527         mov     GSYM(GNAME(os_vm_page_size)),%r9
528 #else
529         mov     os_vm_page_size,%r9
530 #endif
531         lea     (%rsi,%r9), %r8
532         lea     (%rdx,%r9), %r9
533
534         /* Now we begin our main scrub loop. */
535 ascs_outer_loop:
536
537         /* If we're about to scrub the hard guard page, exit. */
538         cmp     %r9, %rax
539         jae     ascs_check_guard_page
540         cmp     %rax, %rdx
541         jbe     ascs_finished
542
543 ascs_check_guard_page:
544         /* If we're about to scrub the guard page, and the guard
545          * page is protected, exit. */
546         cmp     %r8, %rax
547         jae     ascs_clear_loop
548         cmp     %rax, %rsi
549         ja      ascs_clear_loop
550         cmpq    $(NIL), THREAD_CONTROL_STACK_GUARD_PAGE_PROTECTED_OFFSET(%rdi)
551         jne     ascs_finished
552
553         /* Clear memory backwards to the start of the (4KiB) page */
554 ascs_clear_loop:
555         movq    $0, (%rax)
556         test    $0xfff, %rax
557         lea     -8(%rax), %rax
558         jnz     ascs_clear_loop
559
560         /* If we're about to hit the hard guard page, exit. */
561         cmp     %r9, %rax
562         jae     ascs_finished
563
564         /* If the next (previous?) 4KiB page contains a non-zero
565          * word, continue scrubbing. */
566 ascs_check_loop:
567         testq   $-1, (%rax)
568         jnz     ascs_outer_loop
569         test    $0xfff, %rax
570         lea     -8(%rax), %rax
571         jnz     ascs_check_loop
572
573 ascs_finished:
574         ret
575         SIZE(GNAME(arch_scrub_control_stack))
576 \f
577         END()