34b9df5b688f2a719ce636594afda3dd27559d2f
[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 #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_UD2_BREAKPOINTS)
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         push    %rbp            # Save old frame pointer.
109         mov     %rsp,%rbp       # Establish new frame.
110
111         push    %rsi            # args are going in here
112         push    %rdi
113         mov     16(%rbp),%rdi
114         mov     24(%rbp),%rsi
115         mov     32(%rbp),%rdx
116         mov     40(%rbp),%rcx
117         mov     48(%rbp),%rcx
118         mov     56(%rbp),%r8
119         mov     64(%rbp),%r9
120         call    *%rax
121         mov     %rbp,%rsp
122         pop     %rbp
123         ret
124         SIZE(GNAME(call_into_c))
125
126 \f
127         .text   
128         .globl  GNAME(call_into_lisp_first_time)
129         TYPE(GNAME(call_into_lisp_first_time))
130                 
131 /* We don't worry too much about saving registers 
132  * here, because we never expect to return from the initial call to lisp 
133  * anyway */
134         
135         .align  align_16byte,0x90
136 GNAME(call_into_lisp_first_time):
137         push    %rbp            # Save old frame pointer.
138         mov     %rsp,%rbp       # Establish new frame.
139 #if defined(LISP_FEATURE_DARWIN)
140         movq    GSYM(GNAME(all_threads)),%rax
141 #else
142         movq    GNAME(all_threads),%rax
143 #endif
144         mov     THREAD_CONTROL_STACK_END_OFFSET(%rax) ,%rsp
145         jmp     Lstack
146 \f
147         .text   
148         .globl  GNAME(call_into_lisp)
149         TYPE(GNAME(call_into_lisp))
150                 
151 /*
152  * amd64 calling convention: C expects that
153  * arguments go in rdi rsi rdx rcx r8 r9
154  * return values in rax rdx
155  * callee saves rbp rbx r12-15 if it uses them
156  */
157         
158         .align  align_16byte,0x90
159 GNAME(call_into_lisp):
160         push    %rbp            # Save old frame pointer.
161         mov     %rsp,%rbp       # Establish new frame.
162 Lstack:
163         /* FIXME x86 saves FPU state here */
164         push    %rbx    # these regs are callee-saved according to C
165         push    %r12    # so must be preserved and restored when 
166         push    %r13    # the lisp function returns
167         push    %r14    #
168         push    %r15    #
169
170         mov     %rsp,%rbx       # remember current stack
171         push    %rbx            # Save entry stack on (maybe) new stack.
172
173         push    %rdi    # args from C
174         push    %rsi    #
175         push    %rdx    #
176 #ifdef LISP_FEATURE_SB_THREAD
177 #ifdef LISP_FEATURE_GCC_TLS
178         movq    %fs:0, %rax
179         movq    GNAME(current_thread)@TPOFF(%rax), %r12
180 #else
181 #ifdef LISP_FEATURE_DARWIN
182         mov     GSYM(GNAME(specials)),%rdi
183 #else
184         mov     specials,%rdi
185 #endif
186         call    GNAME(pthread_getspecific)
187         mov     %rax,%r12
188 #endif
189 #endif
190         pop     %rcx    # num args
191         pop     %rbx    # arg vector
192         pop     %rax    # function ptr/lexenv
193
194         xor     %rdx,%rdx       # clear any descriptor registers 
195         xor     %rdi,%rdi       # that we can't be sure we'll 
196         xor     %rsi,%rsi       # initialise properly.  XX do r8-r15 too?
197         shl     $(N_FIXNUM_TAG_BITS),%rcx       # (fixnumize num-args)
198         cmp     $0,%rcx
199         je      Ldone
200         mov     0(%rbx),%rdx    # arg0
201         cmp     $8,%rcx
202         je      Ldone
203         mov     8(%rbx),%rdi    # arg1
204         cmp     $16,%rcx
205         je      Ldone
206         mov     16(%rbx),%rsi   # arg2
207 Ldone:  
208         /* Registers rax, rcx, rdx, rdi, and rsi are now live. */
209         xor     %rbx,%rbx       # available
210
211         /* Alloc new frame. */
212         push    %rbp            # Dummy for return address
213         push    %rbp            # fp in save location S1
214         mov     %rsp,%rbp       # The current sp marks start of new frame.
215         sub     $8,%rsp         # Ensure 3 slots are allocated, two above.
216
217 Lcall:
218         call    *CLOSURE_FUN_OFFSET(%rax)
219         
220         /* If the function returned multiple values, it will return to
221            this point.  Lose them */
222         jnc     LsingleValue    
223         mov     %rbx, %rsp
224 LsingleValue:   
225
226 /* Restore the stack, in case there was a stack change. */
227         pop     %rsp            # c-sp
228
229 /* Restore C regs */
230         pop     %r15
231         pop     %r14
232         pop     %r13
233         pop     %r12
234         pop     %rbx
235
236 /* FIXME Restore the NPX state. */
237
238         mov     %rdx,%rax       # c-val
239         leave
240         ret
241         SIZE(GNAME(call_into_lisp))
242 \f
243 /* support for saving and restoring the NPX state from C */
244         .text
245         .globl  GNAME(fpu_save)
246         TYPE(GNAME(fpu_save))
247         .align  align_16byte,0x90
248 GNAME(fpu_save):
249         fnsave  (%rdi)          # Save the NPX state. (resets NPX)
250         ret
251         SIZE(GNAME(fpu_save))
252
253         .globl  GNAME(fpu_restore)
254         TYPE(GNAME(fpu_restore))
255         .align  align_16byte,0x90
256 GNAME(fpu_restore):
257         frstor  (%rdi)          # Restore the NPX state.
258         ret
259         SIZE(GNAME(fpu_restore))
260 \f
261 /*
262  * the undefined-function trampoline
263  */
264         .text
265         .align  align_16byte,0x90
266         .globl  GNAME(undefined_tramp)
267         TYPE(GNAME(undefined_tramp))
268 GNAME(undefined_tramp):
269         pop     8(%rbp)         # Save return PC for backtrace.
270         TRAP
271         .byte   trap_Error
272         .byte   2
273         .byte   UNDEFINED_FUN_ERROR
274         .byte   sc_DescriptorReg # eax in the Descriptor-reg SC
275         ret
276         SIZE(GNAME(undefined_tramp))
277
278 /* KLUDGE: FIND-ESCAPED-FRAME (SYS:SRC;CODE;DEBUG-INT.LISP) needs
279  * to know the name of the function immediately following the
280  * undefined-function trampoline. */
281
282         .text
283         .align  align_16byte,0x90
284         .globl  GNAME(alloc_tramp)
285         TYPE(GNAME(alloc_tramp))
286 GNAME(alloc_tramp):
287         push    %rbp            # Save old frame pointer.
288         mov     %rsp,%rbp       # Establish new frame.
289         push    %rax
290         push    %rcx
291         push    %rdx
292         push    %rsi
293         push    %rdi
294         push    %r8
295         push    %r9
296         push    %r10
297         push    %r11
298         mov     16(%rbp),%rdi   
299         call    GNAME(alloc)
300         mov     %rax,16(%rbp)
301         pop     %r11
302         pop     %r10
303         pop     %r9
304         pop     %r8
305         pop     %rdi
306         pop     %rsi
307         pop     %rdx
308         pop     %rcx
309         pop     %rax
310         pop     %rbp
311         ret
312         SIZE(GNAME(alloc_tramp))
313
314                 
315 /*
316  * the closure trampoline
317  */
318         .text
319         .align  align_16byte,0x90
320         .globl  GNAME(closure_tramp)
321         TYPE(GNAME(closure_tramp))
322 GNAME(closure_tramp):
323         mov     FDEFN_FUN_OFFSET(%rax),%rax
324         /* FIXME: The '*' after "jmp" in the next line is from PVE's
325          * patch posted to the CMU CL mailing list Oct 6, 1999. It looks
326          * reasonable, and it certainly seems as though if CMU CL needs it,
327          * SBCL needs it too, but I haven't actually verified that it's
328          * right. It would be good to find a way to force the flow of
329          * control through here to test it. */
330         jmp     *CLOSURE_FUN_OFFSET(%rax)
331         SIZE(GNAME(closure_tramp))
332
333         .text
334         .align  align_16byte,0x90
335         .globl  GNAME(funcallable_instance_tramp)
336 #if !defined(LISP_FEATURE_DARWIN)
337         .type   GNAME(funcallable_instance_tramp),@function
338 #endif
339         GNAME(funcallable_instance_tramp):
340         mov     FUNCALLABLE_INSTANCE_FUNCTION_OFFSET(%rax),%rax
341         /* KLUDGE: on this platform, whatever kind of function is in %rax
342          * now, the first word of it contains the address to jump to. */
343         jmp     *CLOSURE_FUN_OFFSET(%rax)
344 #if !defined(LISP_FEATURE_DARWIN)
345         .size   GNAME(funcallable_instance_tramp), .-GNAME(funcallable_instance_tramp)
346 #endif
347 /*
348  * fun-end breakpoint magic
349  */
350
351 /*
352  * For an explanation of the magic involved in function-end
353  * breakpoints, see the implementation in ppc-assem.S.
354  */
355
356         .text
357         .globl  GNAME(fun_end_breakpoint_guts)
358         .align  align_16byte
359 GNAME(fun_end_breakpoint_guts):
360         /* Multiple Value return */
361         jc      multiple_value_return
362         /* Single value return: The eventual return will now use the
363            multiple values return convention but with a return values
364            count of one. */
365         mov     %rsp,%rbx       # Setup ebx - the ofp.
366         sub     $8,%rsp         # Allocate one stack slot for the return value
367         mov     $8,%rcx         # Setup ecx for one return value.
368 #if defined(LISP_FEATURE_DARWIN)
369         mov     GSYM(NIL),%rdi  # default second value
370         mov     GSYM(NIL),%rsi  # default third value
371 #else
372         mov     $NIL,%rdi       # default second value
373         mov     $NIL,%rsi       # default third value
374 #endif
375 multiple_value_return:
376         
377         .globl  GNAME(fun_end_breakpoint_trap)
378         .align  align_16byte,0x90
379 GNAME(fun_end_breakpoint_trap):
380         TRAP
381         .byte   trap_FunEndBreakpoint
382         hlt                     # We should never return here.
383
384         .globl  GNAME(fun_end_breakpoint_end)
385 GNAME(fun_end_breakpoint_end):
386
387 \f
388         .globl  GNAME(do_pending_interrupt)
389         TYPE(GNAME(do_pending_interrupt))
390         .align  align_16byte,0x90
391 GNAME(do_pending_interrupt):
392         TRAP
393         .byte   trap_PendingInterrupt
394         ret
395         SIZE(GNAME(do_pending_interrupt))
396 \f
397         .globl  GNAME(post_signal_tramp)
398         TYPE(GNAME(post_signal_tramp))
399         .align  align_16byte,0x90
400 GNAME(post_signal_tramp):
401         /* this is notionally the second half of a function whose first half
402          * doesn't exist.  This is where call_into_lisp returns when called 
403          * using return_to_lisp_function */
404         popq %r15
405         popq %r14
406         popq %r13
407         popq %r12
408         popq %r11
409         popq %r10
410         popq %r9
411         popq %r8
412         popq %rdi
413         popq %rsi
414         /* skip RBP and RSP */
415         popq %rbx
416         popq %rdx
417         popq %rcx
418         popq %rax
419         popfq
420         leave
421         ret
422         SIZE(GNAME(post_signal_tramp))
423 \f
424         .text
425         .align  align_16byte,0x90
426         .globl  GNAME(fast_bzero)
427         TYPE(GNAME(fast_bzero))
428         
429 GNAME(fast_bzero):
430         /* A fast routine for zero-filling blocks of memory that are
431          * guaranteed to start and end at a 4096-byte aligned address.
432          */
433         shr $6, %rsi              /* Amount of 64-byte blocks to copy */
434         jz Lend                   /* If none, stop */
435         mov %rsi, %rcx            /* Save start address */
436         movups %xmm7, -16(%rsp)   /* Save XMM register */
437         xorps  %xmm7, %xmm7       /* Zero the XMM register */
438         jmp Lloop
439         .align align_16byte                 
440 Lloop:
441
442         /* Copy the 16 zeroes from xmm7 to memory, 4 times. MOVNTDQ is the
443          * non-caching double-quadword moving variant, i.e. the memory areas
444          * we're touching are not fetched into the L1 cache, since we're just
445          * going to overwrite the memory soon anyway.
446          */
447         movntdq %xmm7, 0(%rdi)
448         movntdq %xmm7, 16(%rdi)
449         movntdq %xmm7, 32(%rdi)
450         movntdq %xmm7, 48(%rdi)
451
452         add $64, %rdi  /* Advance pointer */
453         dec %rsi       /* Decrement 64-byte block count */
454         jnz Lloop
455         mfence         /* Ensure that the writes are globally visible, since
456                         * MOVNTDQ is weakly ordered */
457         movups -16(%rsp), %xmm7 /* Restore the XMM register */
458         prefetcht0 0(%rcx)      /* Prefetch the start of the block into cache,
459                                  * since it's likely to be used immediately. */
460 Lend:        
461         ret
462         SIZE(GNAME(fast_bzero))
463
464 \f
465 /* When LISP_FEATURE_C_STACK_IS_CONTROL_STACK, we cannot safely scrub
466  * the control stack from C, largely due to not knowing where the
467  * active stack frame ends.  On such platforms, we reimplement the
468  * core scrubbing logic in assembly, in this case here:
469  */
470         .text
471         .align  align_16byte,0x90
472         .globl GNAME(arch_scrub_control_stack)
473         TYPE(GNAME(arch_scrub_control_stack))
474 GNAME(arch_scrub_control_stack):
475         /* We are passed three parameters:
476          * A (struct thread *) in RDI,
477          * the address of the guard page in RSI, and
478          * the address of the hard guard page in RDX.
479          * We may trash RAX, RCX, and R8-R11 with impunity.
480          * [RSP] is our return address, [RSP-8] is the first
481          * stack slot to scrub. */
482
483         /* We start by setting up our scrub pointer in RAX, our
484          * guard page upper bound in R8, and our hard guard
485          * page upper bound in R9. */
486         lea     -8(%rsp), %rax
487 #ifdef LISP_FEATURE_DARWIN
488         mov     GSYM(GNAME(os_vm_page_size)),%r9
489 #else
490         mov     os_vm_page_size,%r9
491 #endif
492         lea     (%rsi,%r9), %r8
493         lea     (%rdx,%r9), %r9
494
495         /* Now we begin our main scrub loop. */
496 ascs_outer_loop:
497
498         /* If we're about to scrub the hard guard page, exit. */
499         cmp     %r9, %rax
500         jae     ascs_check_guard_page
501         cmp     %rax, %rdx
502         jbe     ascs_finished
503
504 ascs_check_guard_page:
505         /* If we're about to scrub the guard page, and the guard
506          * page is protected, exit. */
507         cmp     %r8, %rax
508         jae     ascs_clear_loop
509         cmp     %rax, %rsi
510         ja      ascs_clear_loop
511         cmpq    $(NIL), THREAD_CONTROL_STACK_GUARD_PAGE_PROTECTED_OFFSET(%rdi)
512         jne     ascs_finished
513
514         /* Clear memory backwards to the start of the (4KiB) page */
515 ascs_clear_loop:
516         movq    $0, (%rax)
517         test    $0xfff, %rax
518         lea     -8(%rax), %rax
519         jnz     ascs_clear_loop
520
521         /* If we're about to hit the hard guard page, exit. */
522         cmp     %r9, %rax
523         jae     ascs_finished
524
525         /* If the next (previous?) 4KiB page contains a non-zero
526          * word, continue scrubbing. */
527 ascs_check_loop:
528         testq   $-1, (%rax)
529         jnz     ascs_outer_loop
530         test    $0xfff, %rax
531         lea     -8(%rax), %rax
532         jnz     ascs_check_loop
533
534 ascs_finished:
535         ret
536         SIZE(GNAME(arch_scrub_control_stack))
537 \f
538         END()