x86/asm/entry: Rename 'init_tss' to 'cpu_tss'
[linux-2.6-block.git] / arch / x86 / kernel / entry_64.S
1 /*
2  *  linux/arch/x86_64/entry.S
3  *
4  *  Copyright (C) 1991, 1992  Linus Torvalds
5  *  Copyright (C) 2000, 2001, 2002  Andi Kleen SuSE Labs
6  *  Copyright (C) 2000  Pavel Machek <pavel@suse.cz>
7  */
8
9 /*
10  * entry.S contains the system-call and fault low-level handling routines.
11  *
12  * Some of this is documented in Documentation/x86/entry_64.txt
13  *
14  * NOTE: This code handles signal-recognition, which happens every time
15  * after an interrupt and after each system call.
16  *
17  * A note on terminology:
18  * - top of stack: Architecture defined interrupt frame from SS to RIP
19  * at the top of the kernel process stack.
20  * - partial stack frame: partially saved registers up to R11.
21  * - full stack frame: Like partial stack frame, but all register saved.
22  *
23  * Some macro usage:
24  * - CFI macros are used to generate dwarf2 unwind information for better
25  * backtraces. They don't change any code.
26  * - ENTRY/END Define functions in the symbol table.
27  * - FIXUP_TOP_OF_STACK/RESTORE_TOP_OF_STACK - Fix up the hardware stack
28  * frame that is otherwise undefined after a SYSCALL
29  * - TRACE_IRQ_* - Trace hard interrupt state for lock debugging.
30  * - idtentry - Define exception entry points.
31  */
32
33 #include <linux/linkage.h>
34 #include <asm/segment.h>
35 #include <asm/cache.h>
36 #include <asm/errno.h>
37 #include <asm/dwarf2.h>
38 #include <asm/calling.h>
39 #include <asm/asm-offsets.h>
40 #include <asm/msr.h>
41 #include <asm/unistd.h>
42 #include <asm/thread_info.h>
43 #include <asm/hw_irq.h>
44 #include <asm/page_types.h>
45 #include <asm/irqflags.h>
46 #include <asm/paravirt.h>
47 #include <asm/percpu.h>
48 #include <asm/asm.h>
49 #include <asm/context_tracking.h>
50 #include <asm/smap.h>
51 #include <asm/pgtable_types.h>
52 #include <linux/err.h>
53
54 /* Avoid __ASSEMBLER__'ifying <linux/audit.h> just for this.  */
55 #include <linux/elf-em.h>
56 #define AUDIT_ARCH_X86_64       (EM_X86_64|__AUDIT_ARCH_64BIT|__AUDIT_ARCH_LE)
57 #define __AUDIT_ARCH_64BIT 0x80000000
58 #define __AUDIT_ARCH_LE    0x40000000
59
60         .code64
61         .section .entry.text, "ax"
62
63
64 #ifndef CONFIG_PREEMPT
65 #define retint_kernel retint_restore_args
66 #endif
67
68 #ifdef CONFIG_PARAVIRT
69 ENTRY(native_usergs_sysret64)
70         swapgs
71         sysretq
72 ENDPROC(native_usergs_sysret64)
73 #endif /* CONFIG_PARAVIRT */
74
75
76 .macro TRACE_IRQS_IRETQ
77 #ifdef CONFIG_TRACE_IRQFLAGS
78         bt   $9,EFLAGS(%rsp)    /* interrupts off? */
79         jnc  1f
80         TRACE_IRQS_ON
81 1:
82 #endif
83 .endm
84
85 /*
86  * When dynamic function tracer is enabled it will add a breakpoint
87  * to all locations that it is about to modify, sync CPUs, update
88  * all the code, sync CPUs, then remove the breakpoints. In this time
89  * if lockdep is enabled, it might jump back into the debug handler
90  * outside the updating of the IST protection. (TRACE_IRQS_ON/OFF).
91  *
92  * We need to change the IDT table before calling TRACE_IRQS_ON/OFF to
93  * make sure the stack pointer does not get reset back to the top
94  * of the debug stack, and instead just reuses the current stack.
95  */
96 #if defined(CONFIG_DYNAMIC_FTRACE) && defined(CONFIG_TRACE_IRQFLAGS)
97
98 .macro TRACE_IRQS_OFF_DEBUG
99         call debug_stack_set_zero
100         TRACE_IRQS_OFF
101         call debug_stack_reset
102 .endm
103
104 .macro TRACE_IRQS_ON_DEBUG
105         call debug_stack_set_zero
106         TRACE_IRQS_ON
107         call debug_stack_reset
108 .endm
109
110 .macro TRACE_IRQS_IRETQ_DEBUG
111         bt   $9,EFLAGS(%rsp)    /* interrupts off? */
112         jnc  1f
113         TRACE_IRQS_ON_DEBUG
114 1:
115 .endm
116
117 #else
118 # define TRACE_IRQS_OFF_DEBUG           TRACE_IRQS_OFF
119 # define TRACE_IRQS_ON_DEBUG            TRACE_IRQS_ON
120 # define TRACE_IRQS_IRETQ_DEBUG         TRACE_IRQS_IRETQ
121 #endif
122
123 /*
124  * C code is not supposed to know about undefined top of stack. Every time
125  * a C function with an pt_regs argument is called from the SYSCALL based
126  * fast path FIXUP_TOP_OF_STACK is needed.
127  * RESTORE_TOP_OF_STACK syncs the syscall state after any possible ptregs
128  * manipulation.
129  */
130
131         /* %rsp:at FRAMEEND */
132         .macro FIXUP_TOP_OF_STACK tmp offset=0
133         movq PER_CPU_VAR(old_rsp),\tmp
134         movq \tmp,RSP+\offset(%rsp)
135         movq $__USER_DS,SS+\offset(%rsp)
136         movq $__USER_CS,CS+\offset(%rsp)
137         movq RIP+\offset(%rsp),\tmp  /* get rip */
138         movq \tmp,RCX+\offset(%rsp)  /* copy it to rcx as sysret would do */
139         movq R11+\offset(%rsp),\tmp  /* get eflags */
140         movq \tmp,EFLAGS+\offset(%rsp)
141         .endm
142
143         .macro RESTORE_TOP_OF_STACK tmp offset=0
144         movq RSP+\offset(%rsp),\tmp
145         movq \tmp,PER_CPU_VAR(old_rsp)
146         movq EFLAGS+\offset(%rsp),\tmp
147         movq \tmp,R11+\offset(%rsp)
148         .endm
149
150 /*
151  * empty frame
152  */
153         .macro EMPTY_FRAME start=1 offset=0
154         .if \start
155         CFI_STARTPROC simple
156         CFI_SIGNAL_FRAME
157         CFI_DEF_CFA rsp,8+\offset
158         .else
159         CFI_DEF_CFA_OFFSET 8+\offset
160         .endif
161         .endm
162
163 /*
164  * initial frame state for interrupts (and exceptions without error code)
165  */
166         .macro INTR_FRAME start=1 offset=0
167         EMPTY_FRAME \start, 5*8+\offset
168         /*CFI_REL_OFFSET ss, 4*8+\offset*/
169         CFI_REL_OFFSET rsp, 3*8+\offset
170         /*CFI_REL_OFFSET rflags, 2*8+\offset*/
171         /*CFI_REL_OFFSET cs, 1*8+\offset*/
172         CFI_REL_OFFSET rip, 0*8+\offset
173         .endm
174
175 /*
176  * initial frame state for exceptions with error code (and interrupts
177  * with vector already pushed)
178  */
179         .macro XCPT_FRAME start=1 offset=0
180         INTR_FRAME \start, 1*8+\offset
181         .endm
182
183 /*
184  * frame that enables passing a complete pt_regs to a C function.
185  */
186         .macro DEFAULT_FRAME start=1 offset=0
187         XCPT_FRAME \start, ORIG_RAX+\offset
188         CFI_REL_OFFSET rdi, RDI+\offset
189         CFI_REL_OFFSET rsi, RSI+\offset
190         CFI_REL_OFFSET rdx, RDX+\offset
191         CFI_REL_OFFSET rcx, RCX+\offset
192         CFI_REL_OFFSET rax, RAX+\offset
193         CFI_REL_OFFSET r8, R8+\offset
194         CFI_REL_OFFSET r9, R9+\offset
195         CFI_REL_OFFSET r10, R10+\offset
196         CFI_REL_OFFSET r11, R11+\offset
197         CFI_REL_OFFSET rbx, RBX+\offset
198         CFI_REL_OFFSET rbp, RBP+\offset
199         CFI_REL_OFFSET r12, R12+\offset
200         CFI_REL_OFFSET r13, R13+\offset
201         CFI_REL_OFFSET r14, R14+\offset
202         CFI_REL_OFFSET r15, R15+\offset
203         .endm
204
205 /*
206  * 64bit SYSCALL instruction entry. Up to 6 arguments in registers.
207  *
208  * 64bit SYSCALL saves rip to rcx, clears rflags.RF, then saves rflags to r11,
209  * then loads new ss, cs, and rip from previously programmed MSRs.
210  * rflags gets masked by a value from another MSR (so CLD and CLAC
211  * are not needed). SYSCALL does not save anything on the stack
212  * and does not change rsp.
213  *
214  * Registers on entry:
215  * rax  system call number
216  * rcx  return address
217  * r11  saved rflags (note: r11 is callee-clobbered register in C ABI)
218  * rdi  arg0
219  * rsi  arg1
220  * rdx  arg2
221  * r10  arg3 (needs to be moved to rcx to conform to C ABI)
222  * r8   arg4
223  * r9   arg5
224  * (note: r12-r15,rbp,rbx are callee-preserved in C ABI)
225  *
226  * Interrupts are off on entry.
227  * Only called from user space.
228  *
229  * XXX  if we had a free scratch register we could save the RSP into the stack frame
230  *      and report it properly in ps. Unfortunately we haven't.
231  *
232  * When user can change the frames always force IRET. That is because
233  * it deals with uncanonical addresses better. SYSRET has trouble
234  * with them due to bugs in both AMD and Intel CPUs.
235  */
236
237 ENTRY(system_call)
238         CFI_STARTPROC   simple
239         CFI_SIGNAL_FRAME
240         CFI_DEF_CFA     rsp,KERNEL_STACK_OFFSET
241         CFI_REGISTER    rip,rcx
242         /*CFI_REGISTER  rflags,r11*/
243         SWAPGS_UNSAFE_STACK
244         /*
245          * A hypervisor implementation might want to use a label
246          * after the swapgs, so that it can do the swapgs
247          * for the guest and jump here on syscall.
248          */
249 GLOBAL(system_call_after_swapgs)
250
251         movq    %rsp,PER_CPU_VAR(old_rsp)
252         /* kernel_stack is set so that 5 slots (iret frame) are preallocated */
253         movq    PER_CPU_VAR(kernel_stack),%rsp
254         /*
255          * No need to follow this irqs off/on section - it's straight
256          * and short:
257          */
258         ENABLE_INTERRUPTS(CLBR_NONE)
259         ALLOC_PT_GPREGS_ON_STACK 8              /* +8: space for orig_ax */
260         SAVE_C_REGS_EXCEPT_RAX_RCX
261         movq    $-ENOSYS,RAX(%rsp)
262         movq_cfi rax,ORIG_RAX
263         movq    %rcx,RIP(%rsp)
264         CFI_REL_OFFSET rip,RIP
265         testl $_TIF_WORK_SYSCALL_ENTRY,TI_flags+THREAD_INFO(%rsp,RIP)
266         jnz tracesys
267 system_call_fastpath:
268 #if __SYSCALL_MASK == ~0
269         cmpq $__NR_syscall_max,%rax
270 #else
271         andl $__SYSCALL_MASK,%eax
272         cmpl $__NR_syscall_max,%eax
273 #endif
274         ja ret_from_sys_call  /* and return regs->ax */
275         movq %r10,%rcx
276         call *sys_call_table(,%rax,8)  # XXX:    rip relative
277         movq %rax,RAX(%rsp)
278 /*
279  * Syscall return path ending with SYSRET (fast path)
280  * Has incomplete stack frame and undefined top of stack.
281  */
282 ret_from_sys_call:
283         testl $_TIF_ALLWORK_MASK,TI_flags+THREAD_INFO(%rsp,RIP)
284         jnz int_ret_from_sys_call_fixup /* Go the the slow path */
285
286         LOCKDEP_SYS_EXIT
287         DISABLE_INTERRUPTS(CLBR_NONE)
288         TRACE_IRQS_OFF
289         CFI_REMEMBER_STATE
290         /*
291          * sysretq will re-enable interrupts:
292          */
293         TRACE_IRQS_ON
294         RESTORE_C_REGS_EXCEPT_RCX
295         movq RIP(%rsp),%rcx
296         CFI_REGISTER    rip,rcx
297         /*CFI_REGISTER  rflags,r11*/
298         movq    PER_CPU_VAR(old_rsp), %rsp
299         /*
300          * 64bit SYSRET restores rip from rcx,
301          * rflags from r11 (but RF and VM bits are forced to 0),
302          * cs and ss are loaded from MSRs.
303          */
304         USERGS_SYSRET64
305
306         CFI_RESTORE_STATE
307
308 int_ret_from_sys_call_fixup:
309         FIXUP_TOP_OF_STACK %r11
310         jmp int_ret_from_sys_call
311
312         /* Do syscall tracing */
313 tracesys:
314         movq %rsp, %rdi
315         movq $AUDIT_ARCH_X86_64, %rsi
316         call syscall_trace_enter_phase1
317         test %rax, %rax
318         jnz tracesys_phase2             /* if needed, run the slow path */
319         RESTORE_C_REGS_EXCEPT_RAX       /* else restore clobbered regs */
320         movq ORIG_RAX(%rsp), %rax
321         jmp system_call_fastpath        /*      and return to the fast path */
322
323 tracesys_phase2:
324         SAVE_EXTRA_REGS
325         FIXUP_TOP_OF_STACK %rdi
326         movq %rsp, %rdi
327         movq $AUDIT_ARCH_X86_64, %rsi
328         movq %rax,%rdx
329         call syscall_trace_enter_phase2
330
331         /*
332          * Reload registers from stack in case ptrace changed them.
333          * We don't reload %rax because syscall_trace_entry_phase2() returned
334          * the value it wants us to use in the table lookup.
335          */
336         RESTORE_C_REGS_EXCEPT_RAX
337         RESTORE_EXTRA_REGS
338 #if __SYSCALL_MASK == ~0
339         cmpq $__NR_syscall_max,%rax
340 #else
341         andl $__SYSCALL_MASK,%eax
342         cmpl $__NR_syscall_max,%eax
343 #endif
344         ja   int_ret_from_sys_call      /* RAX(%rsp) is already set */
345         movq %r10,%rcx  /* fixup for C */
346         call *sys_call_table(,%rax,8)
347         movq %rax,RAX(%rsp)
348         /* Use IRET because user could have changed frame */
349
350 /*
351  * Syscall return path ending with IRET.
352  * Has correct top of stack, but partial stack frame.
353  */
354 GLOBAL(int_ret_from_sys_call)
355         DISABLE_INTERRUPTS(CLBR_NONE)
356         TRACE_IRQS_OFF
357         movl $_TIF_ALLWORK_MASK,%edi
358         /* edi: mask to check */
359 GLOBAL(int_with_check)
360         LOCKDEP_SYS_EXIT_IRQ
361         GET_THREAD_INFO(%rcx)
362         movl TI_flags(%rcx),%edx
363         andl %edi,%edx
364         jnz   int_careful
365         andl    $~TS_COMPAT,TI_status(%rcx)
366         jmp   retint_swapgs
367
368         /* Either reschedule or signal or syscall exit tracking needed. */
369         /* First do a reschedule test. */
370         /* edx: work, edi: workmask */
371 int_careful:
372         bt $TIF_NEED_RESCHED,%edx
373         jnc  int_very_careful
374         TRACE_IRQS_ON
375         ENABLE_INTERRUPTS(CLBR_NONE)
376         pushq_cfi %rdi
377         SCHEDULE_USER
378         popq_cfi %rdi
379         DISABLE_INTERRUPTS(CLBR_NONE)
380         TRACE_IRQS_OFF
381         jmp int_with_check
382
383         /* handle signals and tracing -- both require a full stack frame */
384 int_very_careful:
385         TRACE_IRQS_ON
386         ENABLE_INTERRUPTS(CLBR_NONE)
387         SAVE_EXTRA_REGS
388         /* Check for syscall exit trace */
389         testl $_TIF_WORK_SYSCALL_EXIT,%edx
390         jz int_signal
391         pushq_cfi %rdi
392         leaq 8(%rsp),%rdi       # &ptregs -> arg1
393         call syscall_trace_leave
394         popq_cfi %rdi
395         andl $~(_TIF_WORK_SYSCALL_EXIT|_TIF_SYSCALL_EMU),%edi
396         jmp int_restore_rest
397
398 int_signal:
399         testl $_TIF_DO_NOTIFY_MASK,%edx
400         jz 1f
401         movq %rsp,%rdi          # &ptregs -> arg1
402         xorl %esi,%esi          # oldset -> arg2
403         call do_notify_resume
404 1:      movl $_TIF_WORK_MASK,%edi
405 int_restore_rest:
406         RESTORE_EXTRA_REGS
407         DISABLE_INTERRUPTS(CLBR_NONE)
408         TRACE_IRQS_OFF
409         jmp int_with_check
410         CFI_ENDPROC
411 END(system_call)
412
413         .macro FORK_LIKE func
414 ENTRY(stub_\func)
415         CFI_STARTPROC
416         DEFAULT_FRAME 0, 8              /* offset 8: return address */
417         SAVE_EXTRA_REGS 8
418         FIXUP_TOP_OF_STACK %r11, 8
419         call sys_\func
420         RESTORE_TOP_OF_STACK %r11, 8
421         ret
422         CFI_ENDPROC
423 END(stub_\func)
424         .endm
425
426         .macro FIXED_FRAME label,func
427 ENTRY(\label)
428         CFI_STARTPROC
429         DEFAULT_FRAME 0, 8              /* offset 8: return address */
430         FIXUP_TOP_OF_STACK %r11, 8
431         call \func
432         RESTORE_TOP_OF_STACK %r11, 8
433         ret
434         CFI_ENDPROC
435 END(\label)
436         .endm
437
438         FORK_LIKE  clone
439         FORK_LIKE  fork
440         FORK_LIKE  vfork
441         FIXED_FRAME stub_iopl, sys_iopl
442
443 ENTRY(stub_execve)
444         CFI_STARTPROC
445         addq $8, %rsp
446         DEFAULT_FRAME 0
447         SAVE_EXTRA_REGS
448         FIXUP_TOP_OF_STACK %r11
449         call sys_execve
450         movq %rax,RAX(%rsp)
451         RESTORE_EXTRA_REGS
452         jmp int_ret_from_sys_call
453         CFI_ENDPROC
454 END(stub_execve)
455
456 ENTRY(stub_execveat)
457         CFI_STARTPROC
458         addq $8, %rsp
459         DEFAULT_FRAME 0
460         SAVE_EXTRA_REGS
461         FIXUP_TOP_OF_STACK %r11
462         call sys_execveat
463         RESTORE_TOP_OF_STACK %r11
464         movq %rax,RAX(%rsp)
465         RESTORE_EXTRA_REGS
466         jmp int_ret_from_sys_call
467         CFI_ENDPROC
468 END(stub_execveat)
469
470 /*
471  * sigreturn is special because it needs to restore all registers on return.
472  * This cannot be done with SYSRET, so use the IRET return path instead.
473  */
474 ENTRY(stub_rt_sigreturn)
475         CFI_STARTPROC
476         addq $8, %rsp
477         DEFAULT_FRAME 0
478         SAVE_EXTRA_REGS
479         FIXUP_TOP_OF_STACK %r11
480         call sys_rt_sigreturn
481         movq %rax,RAX(%rsp) # fixme, this could be done at the higher layer
482         RESTORE_EXTRA_REGS
483         jmp int_ret_from_sys_call
484         CFI_ENDPROC
485 END(stub_rt_sigreturn)
486
487 #ifdef CONFIG_X86_X32_ABI
488 ENTRY(stub_x32_rt_sigreturn)
489         CFI_STARTPROC
490         addq $8, %rsp
491         DEFAULT_FRAME 0
492         SAVE_EXTRA_REGS
493         FIXUP_TOP_OF_STACK %r11
494         call sys32_x32_rt_sigreturn
495         movq %rax,RAX(%rsp) # fixme, this could be done at the higher layer
496         RESTORE_EXTRA_REGS
497         jmp int_ret_from_sys_call
498         CFI_ENDPROC
499 END(stub_x32_rt_sigreturn)
500
501 ENTRY(stub_x32_execve)
502         CFI_STARTPROC
503         addq $8, %rsp
504         DEFAULT_FRAME 0
505         SAVE_EXTRA_REGS
506         FIXUP_TOP_OF_STACK %r11
507         call compat_sys_execve
508         RESTORE_TOP_OF_STACK %r11
509         movq %rax,RAX(%rsp)
510         RESTORE_EXTRA_REGS
511         jmp int_ret_from_sys_call
512         CFI_ENDPROC
513 END(stub_x32_execve)
514
515 ENTRY(stub_x32_execveat)
516         CFI_STARTPROC
517         addq $8, %rsp
518         DEFAULT_FRAME 0
519         SAVE_EXTRA_REGS
520         FIXUP_TOP_OF_STACK %r11
521         call compat_sys_execveat
522         RESTORE_TOP_OF_STACK %r11
523         movq %rax,RAX(%rsp)
524         RESTORE_EXTRA_REGS
525         jmp int_ret_from_sys_call
526         CFI_ENDPROC
527 END(stub_x32_execveat)
528
529 #endif
530
531 /*
532  * A newly forked process directly context switches into this address.
533  *
534  * rdi: prev task we switched from
535  */
536 ENTRY(ret_from_fork)
537         DEFAULT_FRAME
538
539         LOCK ; btr $TIF_FORK,TI_flags(%r8)
540
541         pushq_cfi $0x0002
542         popfq_cfi                               # reset kernel eflags
543
544         call schedule_tail                      # rdi: 'prev' task parameter
545
546         GET_THREAD_INFO(%rcx)
547
548         RESTORE_EXTRA_REGS
549
550         testl $3,CS(%rsp)                       # from kernel_thread?
551         jz   1f
552
553         /*
554          * By the time we get here, we have no idea whether our pt_regs,
555          * ti flags, and ti status came from the 64-bit SYSCALL fast path,
556          * the slow path, or one of the ia32entry paths.
557          * Use int_ret_from_sys_call to return, since it can safely handle
558          * all of the above.
559          */
560         jmp  int_ret_from_sys_call
561
562 1:
563         movq %rbp, %rdi
564         call *%rbx
565         movl $0, RAX(%rsp)
566         RESTORE_EXTRA_REGS
567         jmp int_ret_from_sys_call
568         CFI_ENDPROC
569 END(ret_from_fork)
570
571 /*
572  * Build the entry stubs and pointer table with some assembler magic.
573  * We pack 7 stubs into a single 32-byte chunk, which will fit in a
574  * single cache line on all modern x86 implementations.
575  */
576         .section .init.rodata,"a"
577 ENTRY(interrupt)
578         .section .entry.text
579         .p2align 5
580         .p2align CONFIG_X86_L1_CACHE_SHIFT
581 ENTRY(irq_entries_start)
582         INTR_FRAME
583 vector=FIRST_EXTERNAL_VECTOR
584 .rept (FIRST_SYSTEM_VECTOR-FIRST_EXTERNAL_VECTOR+6)/7
585         .balign 32
586   .rept 7
587     .if vector < FIRST_SYSTEM_VECTOR
588       .if vector <> FIRST_EXTERNAL_VECTOR
589         CFI_ADJUST_CFA_OFFSET -8
590       .endif
591 1:      pushq_cfi $(~vector+0x80)       /* Note: always in signed byte range */
592       .if ((vector-FIRST_EXTERNAL_VECTOR)%7) <> 6
593         jmp 2f
594       .endif
595       .previous
596         .quad 1b
597       .section .entry.text
598 vector=vector+1
599     .endif
600   .endr
601 2:      jmp common_interrupt
602 .endr
603         CFI_ENDPROC
604 END(irq_entries_start)
605
606 .previous
607 END(interrupt)
608 .previous
609
610 /*
611  * Interrupt entry/exit.
612  *
613  * Interrupt entry points save only callee clobbered registers in fast path.
614  *
615  * Entry runs with interrupts off.
616  */
617
618 /* 0(%rsp): ~(interrupt number) */
619         .macro interrupt func
620         cld
621         /*
622          * Since nothing in interrupt handling code touches r12...r15 members
623          * of "struct pt_regs", and since interrupts can nest, we can save
624          * four stack slots and simultaneously provide
625          * an unwind-friendly stack layout by saving "truncated" pt_regs
626          * exactly up to rbp slot, without these members.
627          */
628         ALLOC_PT_GPREGS_ON_STACK -RBP
629         SAVE_C_REGS -RBP
630         /* this goes to 0(%rsp) for unwinder, not for saving the value: */
631         SAVE_EXTRA_REGS_RBP -RBP
632
633         leaq -RBP(%rsp),%rdi    /* arg1 for \func (pointer to pt_regs) */
634
635         testl $3, CS-RBP(%rsp)
636         je 1f
637         SWAPGS
638 1:
639         /*
640          * Save previous stack pointer, optionally switch to interrupt stack.
641          * irq_count is used to check if a CPU is already on an interrupt stack
642          * or not. While this is essentially redundant with preempt_count it is
643          * a little cheaper to use a separate counter in the PDA (short of
644          * moving irq_enter into assembly, which would be too much work)
645          */
646         movq %rsp, %rsi
647         incl PER_CPU_VAR(irq_count)
648         cmovzq PER_CPU_VAR(irq_stack_ptr),%rsp
649         CFI_DEF_CFA_REGISTER    rsi
650         pushq %rsi
651         /*
652          * For debugger:
653          * "CFA (Current Frame Address) is the value on stack + offset"
654          */
655         CFI_ESCAPE      0x0f /* DW_CFA_def_cfa_expression */, 6, \
656                         0x77 /* DW_OP_breg7 (rsp) */, 0, \
657                         0x06 /* DW_OP_deref */, \
658                         0x08 /* DW_OP_const1u */, SIZEOF_PTREGS-RBP, \
659                         0x22 /* DW_OP_plus */
660         /* We entered an interrupt context - irqs are off: */
661         TRACE_IRQS_OFF
662
663         call \func
664         .endm
665
666         /*
667          * The interrupt stubs push (~vector+0x80) onto the stack and
668          * then jump to common_interrupt.
669          */
670         .p2align CONFIG_X86_L1_CACHE_SHIFT
671 common_interrupt:
672         XCPT_FRAME
673         ASM_CLAC
674         addq $-0x80,(%rsp)              /* Adjust vector to [-256,-1] range */
675         interrupt do_IRQ
676         /* 0(%rsp): old_rsp */
677 ret_from_intr:
678         DISABLE_INTERRUPTS(CLBR_NONE)
679         TRACE_IRQS_OFF
680         decl PER_CPU_VAR(irq_count)
681
682         /* Restore saved previous stack */
683         popq %rsi
684         CFI_DEF_CFA rsi,SIZEOF_PTREGS-RBP /* reg/off reset after def_cfa_expr */
685         /* return code expects complete pt_regs - adjust rsp accordingly: */
686         leaq -RBP(%rsi),%rsp
687         CFI_DEF_CFA_REGISTER    rsp
688         CFI_ADJUST_CFA_OFFSET   RBP
689
690 exit_intr:
691         GET_THREAD_INFO(%rcx)
692         testl $3,CS(%rsp)
693         je retint_kernel
694
695         /* Interrupt came from user space */
696         /*
697          * Has a correct top of stack.
698          * %rcx: thread info. Interrupts off.
699          */
700 retint_with_reschedule:
701         movl $_TIF_WORK_MASK,%edi
702 retint_check:
703         LOCKDEP_SYS_EXIT_IRQ
704         movl TI_flags(%rcx),%edx
705         andl %edi,%edx
706         CFI_REMEMBER_STATE
707         jnz  retint_careful
708
709 retint_swapgs:          /* return to user-space */
710         /*
711          * The iretq could re-enable interrupts:
712          */
713         DISABLE_INTERRUPTS(CLBR_ANY)
714         TRACE_IRQS_IRETQ
715
716         /*
717          * Try to use SYSRET instead of IRET if we're returning to
718          * a completely clean 64-bit userspace context.
719          */
720         movq RCX(%rsp),%rcx
721         cmpq %rcx,RIP(%rsp)             /* RCX == RIP */
722         jne opportunistic_sysret_failed
723
724         /*
725          * On Intel CPUs, sysret with non-canonical RCX/RIP will #GP
726          * in kernel space.  This essentially lets the user take over
727          * the kernel, since userspace controls RSP.  It's not worth
728          * testing for canonicalness exactly -- this check detects any
729          * of the 17 high bits set, which is true for non-canonical
730          * or kernel addresses.  (This will pessimize vsyscall=native.
731          * Big deal.)
732          *
733          * If virtual addresses ever become wider, this will need
734          * to be updated to remain correct on both old and new CPUs.
735          */
736         .ifne __VIRTUAL_MASK_SHIFT - 47
737         .error "virtual address width changed -- sysret checks need update"
738         .endif
739         shr $__VIRTUAL_MASK_SHIFT, %rcx
740         jnz opportunistic_sysret_failed
741
742         cmpq $__USER_CS,CS(%rsp)        /* CS must match SYSRET */
743         jne opportunistic_sysret_failed
744
745         movq R11(%rsp),%r11
746         cmpq %r11,EFLAGS(%rsp)          /* R11 == RFLAGS */
747         jne opportunistic_sysret_failed
748
749         testq $X86_EFLAGS_RF,%r11       /* sysret can't restore RF */
750         jnz opportunistic_sysret_failed
751
752         /* nothing to check for RSP */
753
754         cmpq $__USER_DS,SS(%rsp)        /* SS must match SYSRET */
755         jne opportunistic_sysret_failed
756
757         /*
758          * We win!  This label is here just for ease of understanding
759          * perf profiles.  Nothing jumps here.
760          */
761 irq_return_via_sysret:
762         CFI_REMEMBER_STATE
763         /* r11 is already restored (see code above) */
764         RESTORE_C_REGS_EXCEPT_R11
765         movq RSP(%rsp),%rsp
766         USERGS_SYSRET64
767         CFI_RESTORE_STATE
768
769 opportunistic_sysret_failed:
770         SWAPGS
771         jmp restore_args
772
773 retint_restore_args:    /* return to kernel space */
774         DISABLE_INTERRUPTS(CLBR_ANY)
775         /*
776          * The iretq could re-enable interrupts:
777          */
778         TRACE_IRQS_IRETQ
779 restore_args:
780         RESTORE_C_REGS
781         REMOVE_PT_GPREGS_FROM_STACK 8
782
783 irq_return:
784         INTERRUPT_RETURN
785
786 ENTRY(native_iret)
787         /*
788          * Are we returning to a stack segment from the LDT?  Note: in
789          * 64-bit mode SS:RSP on the exception stack is always valid.
790          */
791 #ifdef CONFIG_X86_ESPFIX64
792         testb $4,(SS-RIP)(%rsp)
793         jnz native_irq_return_ldt
794 #endif
795
796 .global native_irq_return_iret
797 native_irq_return_iret:
798         /*
799          * This may fault.  Non-paranoid faults on return to userspace are
800          * handled by fixup_bad_iret.  These include #SS, #GP, and #NP.
801          * Double-faults due to espfix64 are handled in do_double_fault.
802          * Other faults here are fatal.
803          */
804         iretq
805
806 #ifdef CONFIG_X86_ESPFIX64
807 native_irq_return_ldt:
808         pushq_cfi %rax
809         pushq_cfi %rdi
810         SWAPGS
811         movq PER_CPU_VAR(espfix_waddr),%rdi
812         movq %rax,(0*8)(%rdi)   /* RAX */
813         movq (2*8)(%rsp),%rax   /* RIP */
814         movq %rax,(1*8)(%rdi)
815         movq (3*8)(%rsp),%rax   /* CS */
816         movq %rax,(2*8)(%rdi)
817         movq (4*8)(%rsp),%rax   /* RFLAGS */
818         movq %rax,(3*8)(%rdi)
819         movq (6*8)(%rsp),%rax   /* SS */
820         movq %rax,(5*8)(%rdi)
821         movq (5*8)(%rsp),%rax   /* RSP */
822         movq %rax,(4*8)(%rdi)
823         andl $0xffff0000,%eax
824         popq_cfi %rdi
825         orq PER_CPU_VAR(espfix_stack),%rax
826         SWAPGS
827         movq %rax,%rsp
828         popq_cfi %rax
829         jmp native_irq_return_iret
830 #endif
831
832         /* edi: workmask, edx: work */
833 retint_careful:
834         CFI_RESTORE_STATE
835         bt    $TIF_NEED_RESCHED,%edx
836         jnc   retint_signal
837         TRACE_IRQS_ON
838         ENABLE_INTERRUPTS(CLBR_NONE)
839         pushq_cfi %rdi
840         SCHEDULE_USER
841         popq_cfi %rdi
842         GET_THREAD_INFO(%rcx)
843         DISABLE_INTERRUPTS(CLBR_NONE)
844         TRACE_IRQS_OFF
845         jmp retint_check
846
847 retint_signal:
848         testl $_TIF_DO_NOTIFY_MASK,%edx
849         jz    retint_swapgs
850         TRACE_IRQS_ON
851         ENABLE_INTERRUPTS(CLBR_NONE)
852         SAVE_EXTRA_REGS
853         movq $-1,ORIG_RAX(%rsp)
854         xorl %esi,%esi          # oldset
855         movq %rsp,%rdi          # &pt_regs
856         call do_notify_resume
857         RESTORE_EXTRA_REGS
858         DISABLE_INTERRUPTS(CLBR_NONE)
859         TRACE_IRQS_OFF
860         GET_THREAD_INFO(%rcx)
861         jmp retint_with_reschedule
862
863 #ifdef CONFIG_PREEMPT
864         /* Returning to kernel space. Check if we need preemption */
865         /* rcx:  threadinfo. interrupts off. */
866 ENTRY(retint_kernel)
867         cmpl $0,PER_CPU_VAR(__preempt_count)
868         jnz  retint_restore_args
869         bt   $9,EFLAGS(%rsp)    /* interrupts off? */
870         jnc  retint_restore_args
871         call preempt_schedule_irq
872         jmp exit_intr
873 #endif
874         CFI_ENDPROC
875 END(common_interrupt)
876
877 /*
878  * APIC interrupts.
879  */
880 .macro apicinterrupt3 num sym do_sym
881 ENTRY(\sym)
882         INTR_FRAME
883         ASM_CLAC
884         pushq_cfi $~(\num)
885 .Lcommon_\sym:
886         interrupt \do_sym
887         jmp ret_from_intr
888         CFI_ENDPROC
889 END(\sym)
890 .endm
891
892 #ifdef CONFIG_TRACING
893 #define trace(sym) trace_##sym
894 #define smp_trace(sym) smp_trace_##sym
895
896 .macro trace_apicinterrupt num sym
897 apicinterrupt3 \num trace(\sym) smp_trace(\sym)
898 .endm
899 #else
900 .macro trace_apicinterrupt num sym do_sym
901 .endm
902 #endif
903
904 .macro apicinterrupt num sym do_sym
905 apicinterrupt3 \num \sym \do_sym
906 trace_apicinterrupt \num \sym
907 .endm
908
909 #ifdef CONFIG_SMP
910 apicinterrupt3 IRQ_MOVE_CLEANUP_VECTOR \
911         irq_move_cleanup_interrupt smp_irq_move_cleanup_interrupt
912 apicinterrupt3 REBOOT_VECTOR \
913         reboot_interrupt smp_reboot_interrupt
914 #endif
915
916 #ifdef CONFIG_X86_UV
917 apicinterrupt3 UV_BAU_MESSAGE \
918         uv_bau_message_intr1 uv_bau_message_interrupt
919 #endif
920 apicinterrupt LOCAL_TIMER_VECTOR \
921         apic_timer_interrupt smp_apic_timer_interrupt
922 apicinterrupt X86_PLATFORM_IPI_VECTOR \
923         x86_platform_ipi smp_x86_platform_ipi
924
925 #ifdef CONFIG_HAVE_KVM
926 apicinterrupt3 POSTED_INTR_VECTOR \
927         kvm_posted_intr_ipi smp_kvm_posted_intr_ipi
928 #endif
929
930 #ifdef CONFIG_X86_MCE_THRESHOLD
931 apicinterrupt THRESHOLD_APIC_VECTOR \
932         threshold_interrupt smp_threshold_interrupt
933 #endif
934
935 #ifdef CONFIG_X86_THERMAL_VECTOR
936 apicinterrupt THERMAL_APIC_VECTOR \
937         thermal_interrupt smp_thermal_interrupt
938 #endif
939
940 #ifdef CONFIG_SMP
941 apicinterrupt CALL_FUNCTION_SINGLE_VECTOR \
942         call_function_single_interrupt smp_call_function_single_interrupt
943 apicinterrupt CALL_FUNCTION_VECTOR \
944         call_function_interrupt smp_call_function_interrupt
945 apicinterrupt RESCHEDULE_VECTOR \
946         reschedule_interrupt smp_reschedule_interrupt
947 #endif
948
949 apicinterrupt ERROR_APIC_VECTOR \
950         error_interrupt smp_error_interrupt
951 apicinterrupt SPURIOUS_APIC_VECTOR \
952         spurious_interrupt smp_spurious_interrupt
953
954 #ifdef CONFIG_IRQ_WORK
955 apicinterrupt IRQ_WORK_VECTOR \
956         irq_work_interrupt smp_irq_work_interrupt
957 #endif
958
959 /*
960  * Exception entry points.
961  */
962 #define INIT_TSS_IST(x) PER_CPU_VAR(cpu_tss) + (TSS_ist + ((x) - 1) * 8)
963
964 .macro idtentry sym do_sym has_error_code:req paranoid=0 shift_ist=-1
965 ENTRY(\sym)
966         /* Sanity check */
967         .if \shift_ist != -1 && \paranoid == 0
968         .error "using shift_ist requires paranoid=1"
969         .endif
970
971         .if \has_error_code
972         XCPT_FRAME
973         .else
974         INTR_FRAME
975         .endif
976
977         ASM_CLAC
978         PARAVIRT_ADJUST_EXCEPTION_FRAME
979
980         .ifeq \has_error_code
981         pushq_cfi $-1                   /* ORIG_RAX: no syscall to restart */
982         .endif
983
984         ALLOC_PT_GPREGS_ON_STACK
985
986         .if \paranoid
987         .if \paranoid == 1
988         CFI_REMEMBER_STATE
989         testl $3, CS(%rsp)              /* If coming from userspace, switch */
990         jnz 1f                          /* stacks. */
991         .endif
992         call paranoid_entry
993         .else
994         call error_entry
995         .endif
996         /* returned flag: ebx=0: need swapgs on exit, ebx=1: don't need it */
997
998         DEFAULT_FRAME 0
999
1000         .if \paranoid
1001         .if \shift_ist != -1
1002         TRACE_IRQS_OFF_DEBUG            /* reload IDT in case of recursion */
1003         .else
1004         TRACE_IRQS_OFF
1005         .endif
1006         .endif
1007
1008         movq %rsp,%rdi                  /* pt_regs pointer */
1009
1010         .if \has_error_code
1011         movq ORIG_RAX(%rsp),%rsi        /* get error code */
1012         movq $-1,ORIG_RAX(%rsp)         /* no syscall to restart */
1013         .else
1014         xorl %esi,%esi                  /* no error code */
1015         .endif
1016
1017         .if \shift_ist != -1
1018         subq $EXCEPTION_STKSZ, INIT_TSS_IST(\shift_ist)
1019         .endif
1020
1021         call \do_sym
1022
1023         .if \shift_ist != -1
1024         addq $EXCEPTION_STKSZ, INIT_TSS_IST(\shift_ist)
1025         .endif
1026
1027         /* these procedures expect "no swapgs" flag in ebx */
1028         .if \paranoid
1029         jmp paranoid_exit
1030         .else
1031         jmp error_exit
1032         .endif
1033
1034         .if \paranoid == 1
1035         CFI_RESTORE_STATE
1036         /*
1037          * Paranoid entry from userspace.  Switch stacks and treat it
1038          * as a normal entry.  This means that paranoid handlers
1039          * run in real process context if user_mode(regs).
1040          */
1041 1:
1042         call error_entry
1043
1044         DEFAULT_FRAME 0
1045
1046         movq %rsp,%rdi                  /* pt_regs pointer */
1047         call sync_regs
1048         movq %rax,%rsp                  /* switch stack */
1049
1050         movq %rsp,%rdi                  /* pt_regs pointer */
1051
1052         .if \has_error_code
1053         movq ORIG_RAX(%rsp),%rsi        /* get error code */
1054         movq $-1,ORIG_RAX(%rsp)         /* no syscall to restart */
1055         .else
1056         xorl %esi,%esi                  /* no error code */
1057         .endif
1058
1059         call \do_sym
1060
1061         jmp error_exit                  /* %ebx: no swapgs flag */
1062         .endif
1063
1064         CFI_ENDPROC
1065 END(\sym)
1066 .endm
1067
1068 #ifdef CONFIG_TRACING
1069 .macro trace_idtentry sym do_sym has_error_code:req
1070 idtentry trace(\sym) trace(\do_sym) has_error_code=\has_error_code
1071 idtentry \sym \do_sym has_error_code=\has_error_code
1072 .endm
1073 #else
1074 .macro trace_idtentry sym do_sym has_error_code:req
1075 idtentry \sym \do_sym has_error_code=\has_error_code
1076 .endm
1077 #endif
1078
1079 idtentry divide_error do_divide_error has_error_code=0
1080 idtentry overflow do_overflow has_error_code=0
1081 idtentry bounds do_bounds has_error_code=0
1082 idtentry invalid_op do_invalid_op has_error_code=0
1083 idtentry device_not_available do_device_not_available has_error_code=0
1084 idtentry double_fault do_double_fault has_error_code=1 paranoid=2
1085 idtentry coprocessor_segment_overrun do_coprocessor_segment_overrun has_error_code=0
1086 idtentry invalid_TSS do_invalid_TSS has_error_code=1
1087 idtentry segment_not_present do_segment_not_present has_error_code=1
1088 idtentry spurious_interrupt_bug do_spurious_interrupt_bug has_error_code=0
1089 idtentry coprocessor_error do_coprocessor_error has_error_code=0
1090 idtentry alignment_check do_alignment_check has_error_code=1
1091 idtentry simd_coprocessor_error do_simd_coprocessor_error has_error_code=0
1092
1093
1094         /* Reload gs selector with exception handling */
1095         /* edi:  new selector */
1096 ENTRY(native_load_gs_index)
1097         CFI_STARTPROC
1098         pushfq_cfi
1099         DISABLE_INTERRUPTS(CLBR_ANY & ~CLBR_RDI)
1100         SWAPGS
1101 gs_change:
1102         movl %edi,%gs
1103 2:      mfence          /* workaround */
1104         SWAPGS
1105         popfq_cfi
1106         ret
1107         CFI_ENDPROC
1108 END(native_load_gs_index)
1109
1110         _ASM_EXTABLE(gs_change,bad_gs)
1111         .section .fixup,"ax"
1112         /* running with kernelgs */
1113 bad_gs:
1114         SWAPGS                  /* switch back to user gs */
1115         xorl %eax,%eax
1116         movl %eax,%gs
1117         jmp  2b
1118         .previous
1119
1120 /* Call softirq on interrupt stack. Interrupts are off. */
1121 ENTRY(do_softirq_own_stack)
1122         CFI_STARTPROC
1123         pushq_cfi %rbp
1124         CFI_REL_OFFSET rbp,0
1125         mov  %rsp,%rbp
1126         CFI_DEF_CFA_REGISTER rbp
1127         incl PER_CPU_VAR(irq_count)
1128         cmove PER_CPU_VAR(irq_stack_ptr),%rsp
1129         push  %rbp                      # backlink for old unwinder
1130         call __do_softirq
1131         leaveq
1132         CFI_RESTORE             rbp
1133         CFI_DEF_CFA_REGISTER    rsp
1134         CFI_ADJUST_CFA_OFFSET   -8
1135         decl PER_CPU_VAR(irq_count)
1136         ret
1137         CFI_ENDPROC
1138 END(do_softirq_own_stack)
1139
1140 #ifdef CONFIG_XEN
1141 idtentry xen_hypervisor_callback xen_do_hypervisor_callback has_error_code=0
1142
1143 /*
1144  * A note on the "critical region" in our callback handler.
1145  * We want to avoid stacking callback handlers due to events occurring
1146  * during handling of the last event. To do this, we keep events disabled
1147  * until we've done all processing. HOWEVER, we must enable events before
1148  * popping the stack frame (can't be done atomically) and so it would still
1149  * be possible to get enough handler activations to overflow the stack.
1150  * Although unlikely, bugs of that kind are hard to track down, so we'd
1151  * like to avoid the possibility.
1152  * So, on entry to the handler we detect whether we interrupted an
1153  * existing activation in its critical region -- if so, we pop the current
1154  * activation and restart the handler using the previous one.
1155  */
1156 ENTRY(xen_do_hypervisor_callback)   # do_hypervisor_callback(struct *pt_regs)
1157         CFI_STARTPROC
1158 /*
1159  * Since we don't modify %rdi, evtchn_do_upall(struct *pt_regs) will
1160  * see the correct pointer to the pt_regs
1161  */
1162         movq %rdi, %rsp            # we don't return, adjust the stack frame
1163         CFI_ENDPROC
1164         DEFAULT_FRAME
1165 11:     incl PER_CPU_VAR(irq_count)
1166         movq %rsp,%rbp
1167         CFI_DEF_CFA_REGISTER rbp
1168         cmovzq PER_CPU_VAR(irq_stack_ptr),%rsp
1169         pushq %rbp                      # backlink for old unwinder
1170         call xen_evtchn_do_upcall
1171         popq %rsp
1172         CFI_DEF_CFA_REGISTER rsp
1173         decl PER_CPU_VAR(irq_count)
1174 #ifndef CONFIG_PREEMPT
1175         call xen_maybe_preempt_hcall
1176 #endif
1177         jmp  error_exit
1178         CFI_ENDPROC
1179 END(xen_do_hypervisor_callback)
1180
1181 /*
1182  * Hypervisor uses this for application faults while it executes.
1183  * We get here for two reasons:
1184  *  1. Fault while reloading DS, ES, FS or GS
1185  *  2. Fault while executing IRET
1186  * Category 1 we do not need to fix up as Xen has already reloaded all segment
1187  * registers that could be reloaded and zeroed the others.
1188  * Category 2 we fix up by killing the current process. We cannot use the
1189  * normal Linux return path in this case because if we use the IRET hypercall
1190  * to pop the stack frame we end up in an infinite loop of failsafe callbacks.
1191  * We distinguish between categories by comparing each saved segment register
1192  * with its current contents: any discrepancy means we in category 1.
1193  */
1194 ENTRY(xen_failsafe_callback)
1195         INTR_FRAME 1 (6*8)
1196         /*CFI_REL_OFFSET gs,GS*/
1197         /*CFI_REL_OFFSET fs,FS*/
1198         /*CFI_REL_OFFSET es,ES*/
1199         /*CFI_REL_OFFSET ds,DS*/
1200         CFI_REL_OFFSET r11,8
1201         CFI_REL_OFFSET rcx,0
1202         movw %ds,%cx
1203         cmpw %cx,0x10(%rsp)
1204         CFI_REMEMBER_STATE
1205         jne 1f
1206         movw %es,%cx
1207         cmpw %cx,0x18(%rsp)
1208         jne 1f
1209         movw %fs,%cx
1210         cmpw %cx,0x20(%rsp)
1211         jne 1f
1212         movw %gs,%cx
1213         cmpw %cx,0x28(%rsp)
1214         jne 1f
1215         /* All segments match their saved values => Category 2 (Bad IRET). */
1216         movq (%rsp),%rcx
1217         CFI_RESTORE rcx
1218         movq 8(%rsp),%r11
1219         CFI_RESTORE r11
1220         addq $0x30,%rsp
1221         CFI_ADJUST_CFA_OFFSET -0x30
1222         pushq_cfi $0    /* RIP */
1223         pushq_cfi %r11
1224         pushq_cfi %rcx
1225         jmp general_protection
1226         CFI_RESTORE_STATE
1227 1:      /* Segment mismatch => Category 1 (Bad segment). Retry the IRET. */
1228         movq (%rsp),%rcx
1229         CFI_RESTORE rcx
1230         movq 8(%rsp),%r11
1231         CFI_RESTORE r11
1232         addq $0x30,%rsp
1233         CFI_ADJUST_CFA_OFFSET -0x30
1234         pushq_cfi $-1 /* orig_ax = -1 => not a system call */
1235         ALLOC_PT_GPREGS_ON_STACK
1236         SAVE_C_REGS
1237         SAVE_EXTRA_REGS
1238         jmp error_exit
1239         CFI_ENDPROC
1240 END(xen_failsafe_callback)
1241
1242 apicinterrupt3 HYPERVISOR_CALLBACK_VECTOR \
1243         xen_hvm_callback_vector xen_evtchn_do_upcall
1244
1245 #endif /* CONFIG_XEN */
1246
1247 #if IS_ENABLED(CONFIG_HYPERV)
1248 apicinterrupt3 HYPERVISOR_CALLBACK_VECTOR \
1249         hyperv_callback_vector hyperv_vector_handler
1250 #endif /* CONFIG_HYPERV */
1251
1252 idtentry debug do_debug has_error_code=0 paranoid=1 shift_ist=DEBUG_STACK
1253 idtentry int3 do_int3 has_error_code=0 paranoid=1 shift_ist=DEBUG_STACK
1254 idtentry stack_segment do_stack_segment has_error_code=1
1255 #ifdef CONFIG_XEN
1256 idtentry xen_debug do_debug has_error_code=0
1257 idtentry xen_int3 do_int3 has_error_code=0
1258 idtentry xen_stack_segment do_stack_segment has_error_code=1
1259 #endif
1260 idtentry general_protection do_general_protection has_error_code=1
1261 trace_idtentry page_fault do_page_fault has_error_code=1
1262 #ifdef CONFIG_KVM_GUEST
1263 idtentry async_page_fault do_async_page_fault has_error_code=1
1264 #endif
1265 #ifdef CONFIG_X86_MCE
1266 idtentry machine_check has_error_code=0 paranoid=1 do_sym=*machine_check_vector(%rip)
1267 #endif
1268
1269 /*
1270  * Save all registers in pt_regs, and switch gs if needed.
1271  * Use slow, but surefire "are we in kernel?" check.
1272  * Return: ebx=0: need swapgs on exit, ebx=1: otherwise
1273  */
1274 ENTRY(paranoid_entry)
1275         XCPT_FRAME 1 15*8
1276         cld
1277         SAVE_C_REGS 8
1278         SAVE_EXTRA_REGS 8
1279         movl $1,%ebx
1280         movl $MSR_GS_BASE,%ecx
1281         rdmsr
1282         testl %edx,%edx
1283         js 1f   /* negative -> in kernel */
1284         SWAPGS
1285         xorl %ebx,%ebx
1286 1:      ret
1287         CFI_ENDPROC
1288 END(paranoid_entry)
1289
1290 /*
1291  * "Paranoid" exit path from exception stack.  This is invoked
1292  * only on return from non-NMI IST interrupts that came
1293  * from kernel space.
1294  *
1295  * We may be returning to very strange contexts (e.g. very early
1296  * in syscall entry), so checking for preemption here would
1297  * be complicated.  Fortunately, we there's no good reason
1298  * to try to handle preemption here.
1299  */
1300 /* On entry, ebx is "no swapgs" flag (1: don't need swapgs, 0: need it) */
1301 ENTRY(paranoid_exit)
1302         DEFAULT_FRAME
1303         DISABLE_INTERRUPTS(CLBR_NONE)
1304         TRACE_IRQS_OFF_DEBUG
1305         testl %ebx,%ebx                         /* swapgs needed? */
1306         jnz paranoid_exit_no_swapgs
1307         TRACE_IRQS_IRETQ
1308         SWAPGS_UNSAFE_STACK
1309         jmp paranoid_exit_restore
1310 paranoid_exit_no_swapgs:
1311         TRACE_IRQS_IRETQ_DEBUG
1312 paranoid_exit_restore:
1313         RESTORE_EXTRA_REGS
1314         RESTORE_C_REGS
1315         REMOVE_PT_GPREGS_FROM_STACK 8
1316         INTERRUPT_RETURN
1317         CFI_ENDPROC
1318 END(paranoid_exit)
1319
1320 /*
1321  * Save all registers in pt_regs, and switch gs if needed.
1322  * Return: ebx=0: need swapgs on exit, ebx=1: otherwise
1323  */
1324 ENTRY(error_entry)
1325         XCPT_FRAME 1 15*8
1326         cld
1327         SAVE_C_REGS 8
1328         SAVE_EXTRA_REGS 8
1329         xorl %ebx,%ebx
1330         testl $3,CS+8(%rsp)
1331         je error_kernelspace
1332 error_swapgs:
1333         SWAPGS
1334 error_sti:
1335         TRACE_IRQS_OFF
1336         ret
1337
1338         /*
1339          * There are two places in the kernel that can potentially fault with
1340          * usergs. Handle them here.  B stepping K8s sometimes report a
1341          * truncated RIP for IRET exceptions returning to compat mode. Check
1342          * for these here too.
1343          */
1344 error_kernelspace:
1345         CFI_REL_OFFSET rcx, RCX+8
1346         incl %ebx
1347         leaq native_irq_return_iret(%rip),%rcx
1348         cmpq %rcx,RIP+8(%rsp)
1349         je error_bad_iret
1350         movl %ecx,%eax  /* zero extend */
1351         cmpq %rax,RIP+8(%rsp)
1352         je bstep_iret
1353         cmpq $gs_change,RIP+8(%rsp)
1354         je error_swapgs
1355         jmp error_sti
1356
1357 bstep_iret:
1358         /* Fix truncated RIP */
1359         movq %rcx,RIP+8(%rsp)
1360         /* fall through */
1361
1362 error_bad_iret:
1363         SWAPGS
1364         mov %rsp,%rdi
1365         call fixup_bad_iret
1366         mov %rax,%rsp
1367         decl %ebx       /* Return to usergs */
1368         jmp error_sti
1369         CFI_ENDPROC
1370 END(error_entry)
1371
1372
1373 /* On entry, ebx is "no swapgs" flag (1: don't need swapgs, 0: need it) */
1374 ENTRY(error_exit)
1375         DEFAULT_FRAME
1376         movl %ebx,%eax
1377         RESTORE_EXTRA_REGS
1378         DISABLE_INTERRUPTS(CLBR_NONE)
1379         TRACE_IRQS_OFF
1380         GET_THREAD_INFO(%rcx)
1381         testl %eax,%eax
1382         jne retint_kernel
1383         LOCKDEP_SYS_EXIT_IRQ
1384         movl TI_flags(%rcx),%edx
1385         movl $_TIF_WORK_MASK,%edi
1386         andl %edi,%edx
1387         jnz retint_careful
1388         jmp retint_swapgs
1389         CFI_ENDPROC
1390 END(error_exit)
1391
1392 /*
1393  * Test if a given stack is an NMI stack or not.
1394  */
1395         .macro test_in_nmi reg stack nmi_ret normal_ret
1396         cmpq %\reg, \stack
1397         ja \normal_ret
1398         subq $EXCEPTION_STKSZ, %\reg
1399         cmpq %\reg, \stack
1400         jb \normal_ret
1401         jmp \nmi_ret
1402         .endm
1403
1404         /* runs on exception stack */
1405 ENTRY(nmi)
1406         INTR_FRAME
1407         PARAVIRT_ADJUST_EXCEPTION_FRAME
1408         /*
1409          * We allow breakpoints in NMIs. If a breakpoint occurs, then
1410          * the iretq it performs will take us out of NMI context.
1411          * This means that we can have nested NMIs where the next
1412          * NMI is using the top of the stack of the previous NMI. We
1413          * can't let it execute because the nested NMI will corrupt the
1414          * stack of the previous NMI. NMI handlers are not re-entrant
1415          * anyway.
1416          *
1417          * To handle this case we do the following:
1418          *  Check the a special location on the stack that contains
1419          *  a variable that is set when NMIs are executing.
1420          *  The interrupted task's stack is also checked to see if it
1421          *  is an NMI stack.
1422          *  If the variable is not set and the stack is not the NMI
1423          *  stack then:
1424          *    o Set the special variable on the stack
1425          *    o Copy the interrupt frame into a "saved" location on the stack
1426          *    o Copy the interrupt frame into a "copy" location on the stack
1427          *    o Continue processing the NMI
1428          *  If the variable is set or the previous stack is the NMI stack:
1429          *    o Modify the "copy" location to jump to the repeate_nmi
1430          *    o return back to the first NMI
1431          *
1432          * Now on exit of the first NMI, we first clear the stack variable
1433          * The NMI stack will tell any nested NMIs at that point that it is
1434          * nested. Then we pop the stack normally with iret, and if there was
1435          * a nested NMI that updated the copy interrupt stack frame, a
1436          * jump will be made to the repeat_nmi code that will handle the second
1437          * NMI.
1438          */
1439
1440         /* Use %rdx as out temp variable throughout */
1441         pushq_cfi %rdx
1442         CFI_REL_OFFSET rdx, 0
1443
1444         /*
1445          * If %cs was not the kernel segment, then the NMI triggered in user
1446          * space, which means it is definitely not nested.
1447          */
1448         cmpl $__KERNEL_CS, 16(%rsp)
1449         jne first_nmi
1450
1451         /*
1452          * Check the special variable on the stack to see if NMIs are
1453          * executing.
1454          */
1455         cmpl $1, -8(%rsp)
1456         je nested_nmi
1457
1458         /*
1459          * Now test if the previous stack was an NMI stack.
1460          * We need the double check. We check the NMI stack to satisfy the
1461          * race when the first NMI clears the variable before returning.
1462          * We check the variable because the first NMI could be in a
1463          * breakpoint routine using a breakpoint stack.
1464          */
1465         lea 6*8(%rsp), %rdx
1466         test_in_nmi rdx, 4*8(%rsp), nested_nmi, first_nmi
1467         CFI_REMEMBER_STATE
1468
1469 nested_nmi:
1470         /*
1471          * Do nothing if we interrupted the fixup in repeat_nmi.
1472          * It's about to repeat the NMI handler, so we are fine
1473          * with ignoring this one.
1474          */
1475         movq $repeat_nmi, %rdx
1476         cmpq 8(%rsp), %rdx
1477         ja 1f
1478         movq $end_repeat_nmi, %rdx
1479         cmpq 8(%rsp), %rdx
1480         ja nested_nmi_out
1481
1482 1:
1483         /* Set up the interrupted NMIs stack to jump to repeat_nmi */
1484         leaq -1*8(%rsp), %rdx
1485         movq %rdx, %rsp
1486         CFI_ADJUST_CFA_OFFSET 1*8
1487         leaq -10*8(%rsp), %rdx
1488         pushq_cfi $__KERNEL_DS
1489         pushq_cfi %rdx
1490         pushfq_cfi
1491         pushq_cfi $__KERNEL_CS
1492         pushq_cfi $repeat_nmi
1493
1494         /* Put stack back */
1495         addq $(6*8), %rsp
1496         CFI_ADJUST_CFA_OFFSET -6*8
1497
1498 nested_nmi_out:
1499         popq_cfi %rdx
1500         CFI_RESTORE rdx
1501
1502         /* No need to check faults here */
1503         INTERRUPT_RETURN
1504
1505         CFI_RESTORE_STATE
1506 first_nmi:
1507         /*
1508          * Because nested NMIs will use the pushed location that we
1509          * stored in rdx, we must keep that space available.
1510          * Here's what our stack frame will look like:
1511          * +-------------------------+
1512          * | original SS             |
1513          * | original Return RSP     |
1514          * | original RFLAGS         |
1515          * | original CS             |
1516          * | original RIP            |
1517          * +-------------------------+
1518          * | temp storage for rdx    |
1519          * +-------------------------+
1520          * | NMI executing variable  |
1521          * +-------------------------+
1522          * | copied SS               |
1523          * | copied Return RSP       |
1524          * | copied RFLAGS           |
1525          * | copied CS               |
1526          * | copied RIP              |
1527          * +-------------------------+
1528          * | Saved SS                |
1529          * | Saved Return RSP        |
1530          * | Saved RFLAGS            |
1531          * | Saved CS                |
1532          * | Saved RIP               |
1533          * +-------------------------+
1534          * | pt_regs                 |
1535          * +-------------------------+
1536          *
1537          * The saved stack frame is used to fix up the copied stack frame
1538          * that a nested NMI may change to make the interrupted NMI iret jump
1539          * to the repeat_nmi. The original stack frame and the temp storage
1540          * is also used by nested NMIs and can not be trusted on exit.
1541          */
1542         /* Do not pop rdx, nested NMIs will corrupt that part of the stack */
1543         movq (%rsp), %rdx
1544         CFI_RESTORE rdx
1545
1546         /* Set the NMI executing variable on the stack. */
1547         pushq_cfi $1
1548
1549         /*
1550          * Leave room for the "copied" frame
1551          */
1552         subq $(5*8), %rsp
1553         CFI_ADJUST_CFA_OFFSET 5*8
1554
1555         /* Copy the stack frame to the Saved frame */
1556         .rept 5
1557         pushq_cfi 11*8(%rsp)
1558         .endr
1559         CFI_DEF_CFA_OFFSET 5*8
1560
1561         /* Everything up to here is safe from nested NMIs */
1562
1563         /*
1564          * If there was a nested NMI, the first NMI's iret will return
1565          * here. But NMIs are still enabled and we can take another
1566          * nested NMI. The nested NMI checks the interrupted RIP to see
1567          * if it is between repeat_nmi and end_repeat_nmi, and if so
1568          * it will just return, as we are about to repeat an NMI anyway.
1569          * This makes it safe to copy to the stack frame that a nested
1570          * NMI will update.
1571          */
1572 repeat_nmi:
1573         /*
1574          * Update the stack variable to say we are still in NMI (the update
1575          * is benign for the non-repeat case, where 1 was pushed just above
1576          * to this very stack slot).
1577          */
1578         movq $1, 10*8(%rsp)
1579
1580         /* Make another copy, this one may be modified by nested NMIs */
1581         addq $(10*8), %rsp
1582         CFI_ADJUST_CFA_OFFSET -10*8
1583         .rept 5
1584         pushq_cfi -6*8(%rsp)
1585         .endr
1586         subq $(5*8), %rsp
1587         CFI_DEF_CFA_OFFSET 5*8
1588 end_repeat_nmi:
1589
1590         /*
1591          * Everything below this point can be preempted by a nested
1592          * NMI if the first NMI took an exception and reset our iret stack
1593          * so that we repeat another NMI.
1594          */
1595         pushq_cfi $-1           /* ORIG_RAX: no syscall to restart */
1596         ALLOC_PT_GPREGS_ON_STACK
1597
1598         /*
1599          * Use paranoid_entry to handle SWAPGS, but no need to use paranoid_exit
1600          * as we should not be calling schedule in NMI context.
1601          * Even with normal interrupts enabled. An NMI should not be
1602          * setting NEED_RESCHED or anything that normal interrupts and
1603          * exceptions might do.
1604          */
1605         call paranoid_entry
1606         DEFAULT_FRAME 0
1607
1608         /*
1609          * Save off the CR2 register. If we take a page fault in the NMI then
1610          * it could corrupt the CR2 value. If the NMI preempts a page fault
1611          * handler before it was able to read the CR2 register, and then the
1612          * NMI itself takes a page fault, the page fault that was preempted
1613          * will read the information from the NMI page fault and not the
1614          * origin fault. Save it off and restore it if it changes.
1615          * Use the r12 callee-saved register.
1616          */
1617         movq %cr2, %r12
1618
1619         /* paranoidentry do_nmi, 0; without TRACE_IRQS_OFF */
1620         movq %rsp,%rdi
1621         movq $-1,%rsi
1622         call do_nmi
1623
1624         /* Did the NMI take a page fault? Restore cr2 if it did */
1625         movq %cr2, %rcx
1626         cmpq %rcx, %r12
1627         je 1f
1628         movq %r12, %cr2
1629 1:
1630         
1631         testl %ebx,%ebx                         /* swapgs needed? */
1632         jnz nmi_restore
1633 nmi_swapgs:
1634         SWAPGS_UNSAFE_STACK
1635 nmi_restore:
1636         RESTORE_EXTRA_REGS
1637         RESTORE_C_REGS
1638         /* Pop the extra iret frame at once */
1639         REMOVE_PT_GPREGS_FROM_STACK 6*8
1640
1641         /* Clear the NMI executing stack variable */
1642         movq $0, 5*8(%rsp)
1643         jmp irq_return
1644         CFI_ENDPROC
1645 END(nmi)
1646
1647 ENTRY(ignore_sysret)
1648         CFI_STARTPROC
1649         mov $-ENOSYS,%eax
1650         sysret
1651         CFI_ENDPROC
1652 END(ignore_sysret)
1653