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