xref: /freebsd/sys/amd64/amd64/exception.S (revision 7bd6fde3)
1/*-
2 * Copyright (c) 1989, 1990 William F. Jolitz.
3 * Copyright (c) 1990 The Regents of the University of California.
4 * All rights reserved.
5 *
6 * Redistribution and use in source and binary forms, with or without
7 * modification, are permitted provided that the following conditions
8 * are met:
9 * 1. Redistributions of source code must retain the above copyright
10 *    notice, this list of conditions and the following disclaimer.
11 * 2. Redistributions in binary form must reproduce the above copyright
12 *    notice, this list of conditions and the following disclaimer in the
13 *    documentation and/or other materials provided with the distribution.
14 * 4. Neither the name of the University nor the names of its contributors
15 *    may be used to endorse or promote products derived from this software
16 *    without specific prior written permission.
17 *
18 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
19 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
20 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
21 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
22 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
23 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
24 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
25 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
26 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
27 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
28 * SUCH DAMAGE.
29 *
30 * $FreeBSD$
31 */
32
33#include "opt_atpic.h"
34#include "opt_compat.h"
35
36#include <machine/asmacros.h>
37#include <machine/psl.h>
38#include <machine/trap.h>
39
40#include "assym.s"
41
42	.text
43
44/*****************************************************************************/
45/* Trap handling                                                             */
46/*****************************************************************************/
47/*
48 * Trap and fault vector routines.
49 *
50 * All traps are 'interrupt gates', SDT_SYSIGT.  An interrupt gate pushes
51 * state on the stack but also disables interrupts.  This is important for
52 * us for the use of the swapgs instruction.  We cannot be interrupted
53 * until the GS.base value is correct.  For most traps, we automatically
54 * then enable interrupts if the interrupted context had them enabled.
55 * This is equivalent to the i386 port's use of SDT_SYS386TGT.
56 *
57 * The cpu will push a certain amount of state onto the kernel stack for
58 * the current process.  See amd64/include/frame.h.
59 * This includes the current RFLAGS (status register, which includes
60 * the interrupt disable state prior to the trap), the code segment register,
61 * and the return instruction pointer are pushed by the cpu.  The cpu
62 * will also push an 'error' code for certain traps.  We push a dummy
63 * error code for those traps where the cpu doesn't in order to maintain
64 * a consistent frame.  We also push a contrived 'trap number'.
65 *
66 * The cpu does not push the general registers, we must do that, and we
67 * must restore them prior to calling 'iret'.  The cpu adjusts the %cs and
68 * %ss segment registers, but does not mess with %ds, %es, or %fs.  Thus we
69 * must load them with appropriate values for supervisor mode operation.
70 */
71
72MCOUNT_LABEL(user)
73MCOUNT_LABEL(btrap)
74
75/* Traps that we leave interrupts disabled for.. */
76#define	TRAP_NOEN(a)	\
77	subq $TF_RIP,%rsp; \
78	movq $(a),TF_TRAPNO(%rsp) ; \
79	movq $0,TF_ADDR(%rsp) ; \
80	movq $0,TF_ERR(%rsp) ; \
81	jmp alltraps_noen
82IDTVEC(dbg)
83	TRAP_NOEN(T_TRCTRAP)
84IDTVEC(bpt)
85	TRAP_NOEN(T_BPTFLT)
86
87/* Regular traps; The cpu does not supply tf_err for these. */
88#define	TRAP(a)	 \
89	subq $TF_RIP,%rsp; \
90	movq $(a),TF_TRAPNO(%rsp) ; \
91	movq $0,TF_ADDR(%rsp) ; \
92	movq $0,TF_ERR(%rsp) ; \
93	jmp alltraps
94IDTVEC(div)
95	TRAP(T_DIVIDE)
96IDTVEC(ofl)
97	TRAP(T_OFLOW)
98IDTVEC(bnd)
99	TRAP(T_BOUND)
100IDTVEC(ill)
101	TRAP(T_PRIVINFLT)
102IDTVEC(dna)
103	TRAP(T_DNA)
104IDTVEC(fpusegm)
105	TRAP(T_FPOPFLT)
106IDTVEC(mchk)
107	TRAP(T_MCHK)
108IDTVEC(rsvd)
109	TRAP(T_RESERVED)
110IDTVEC(fpu)
111	TRAP(T_ARITHTRAP)
112IDTVEC(xmm)
113	TRAP(T_XMMFLT)
114
115/* This group of traps have tf_err already pushed by the cpu */
116#define	TRAP_ERR(a)	\
117	subq $TF_ERR,%rsp; \
118	movq $(a),TF_TRAPNO(%rsp) ; \
119	movq $0,TF_ADDR(%rsp) ; \
120	jmp alltraps
121IDTVEC(tss)
122	TRAP_ERR(T_TSSFLT)
123IDTVEC(missing)
124	TRAP_ERR(T_SEGNPFLT)
125IDTVEC(stk)
126	TRAP_ERR(T_STKFLT)
127IDTVEC(align)
128	TRAP_ERR(T_ALIGNFLT)
129
130	/*
131	 * alltraps entry point.  Use swapgs if this is the first time in the
132	 * kernel from userland.  Reenable interrupts if they were enabled
133	 * before the trap.  This approximates SDT_SYS386TGT on the i386 port.
134	 */
135
136	SUPERALIGN_TEXT
137	.globl	alltraps
138	.type	alltraps,@function
139alltraps:
140	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
141	jz	alltraps_testi		/* already running with kernel GS.base */
142	swapgs
143alltraps_testi:
144	testl	$PSL_I,TF_RFLAGS(%rsp)
145	jz	alltraps_pushregs
146	sti
147alltraps_pushregs:
148	movq	%rdi,TF_RDI(%rsp)
149alltraps_pushregs_no_rdi:
150	movq	%rsi,TF_RSI(%rsp)
151	movq	%rdx,TF_RDX(%rsp)
152	movq	%rcx,TF_RCX(%rsp)
153	movq	%r8,TF_R8(%rsp)
154	movq	%r9,TF_R9(%rsp)
155	movq	%rax,TF_RAX(%rsp)
156	movq	%rbx,TF_RBX(%rsp)
157	movq	%rbp,TF_RBP(%rsp)
158	movq	%r10,TF_R10(%rsp)
159	movq	%r11,TF_R11(%rsp)
160	movq	%r12,TF_R12(%rsp)
161	movq	%r13,TF_R13(%rsp)
162	movq	%r14,TF_R14(%rsp)
163	movq	%r15,TF_R15(%rsp)
164	FAKE_MCOUNT(TF_RIP(%rsp))
165	.globl	calltrap
166	.type	calltrap,@function
167calltrap:
168	movq	%rsp, %rdi
169	call	trap
170	MEXITCOUNT
171	jmp	doreti			/* Handle any pending ASTs */
172
173	/*
174	 * alltraps_noen entry point.  Unlike alltraps above, we want to
175	 * leave the interrupts disabled.  This corresponds to
176	 * SDT_SYS386IGT on the i386 port.
177	 */
178	SUPERALIGN_TEXT
179	.globl	alltraps_noen
180	.type	alltraps_noen,@function
181alltraps_noen:
182	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
183	jz	alltraps_pushregs	/* already running with kernel GS.base */
184	swapgs
185	jmp	alltraps_pushregs
186
187IDTVEC(dblfault)
188	subq	$TF_ERR,%rsp
189	movq	$T_DOUBLEFLT,TF_TRAPNO(%rsp)
190	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
191	jz	1f			/* already running with kernel GS.base */
192	swapgs
1931:	call	dblfault_handler
1942:	hlt
195	jmp	2b
196
197IDTVEC(page)
198	subq	$TF_ERR,%rsp
199	movq	$T_PAGEFLT,TF_TRAPNO(%rsp)
200	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
201	jz	1f			/* already running with kernel GS.base */
202	swapgs
2031:
204	movq	%rdi,TF_RDI(%rsp)	/* free up a GP register */
205	movq	%cr2,%rdi		/* preserve %cr2 before ..  */
206	movq	%rdi,TF_ADDR(%rsp)	/* enabling interrupts. */
207	testl	$PSL_I,TF_RFLAGS(%rsp)
208	jz	alltraps_pushregs_no_rdi
209	sti
210	jmp	alltraps_pushregs_no_rdi
211
212	/*
213	 * We have to special-case this one.  If we get a trap in doreti() at
214	 * the iretq stage, we'll reenter with the wrong gs state.  We'll have
215	 * to do a special the swapgs in this case even coming from the kernel.
216	 * XXX linux has a trap handler for their equivalent of load_gs().
217	 */
218IDTVEC(prot)
219	subq	$TF_ERR,%rsp
220	movq	$T_PROTFLT,TF_TRAPNO(%rsp)
221	movq	$0,TF_ADDR(%rsp)
222	movq	%rdi,TF_RDI(%rsp)	/* free up a GP register */
223	leaq	doreti_iret(%rip),%rdi
224	cmpq	%rdi,TF_RIP(%rsp)
225	je	2f			/* kernel but with user gsbase!! */
226	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
227	jz	1f			/* already running with kernel GS.base */
2282:
229	swapgs
2301:
231	testl	$PSL_I,TF_RFLAGS(%rsp)
232	jz	alltraps_pushregs_no_rdi
233	sti
234	jmp	alltraps_pushregs_no_rdi
235
236/*
237 * Fast syscall entry point.  We enter here with just our new %cs/%ss set,
238 * and the new privilige level.  We are still running on the old user stack
239 * pointer.  We have to juggle a few things around to find our stack etc.
240 * swapgs gives us access to our PCPU space only.
241 */
242IDTVEC(fast_syscall)
243	swapgs
244	movq	%rsp,PCPU(SCRATCH_RSP)
245	movq	PCPU(RSP0),%rsp
246	/* Now emulate a trapframe. Make the 8 byte alignment odd for call. */
247	subq	$TF_SIZE,%rsp
248	/* defer TF_RSP till we have a spare register */
249	movq	%r11,TF_RFLAGS(%rsp)
250	movq	%rcx,TF_RIP(%rsp)	/* %rcx original value is in %r10 */
251	movq	PCPU(SCRATCH_RSP),%r11	/* %r11 already saved */
252	movq	%r11,TF_RSP(%rsp)	/* user stack pointer */
253	sti
254	movq	$KUDSEL,TF_SS(%rsp)
255	movq	$KUCSEL,TF_CS(%rsp)
256	movq	$2,TF_ERR(%rsp)
257	movq	%rdi,TF_RDI(%rsp)	/* arg 1 */
258	movq	%rsi,TF_RSI(%rsp)	/* arg 2 */
259	movq	%rdx,TF_RDX(%rsp)	/* arg 3 */
260	movq	%r10,TF_RCX(%rsp)	/* arg 4 */
261	movq	%r8,TF_R8(%rsp)		/* arg 5 */
262	movq	%r9,TF_R9(%rsp)		/* arg 6 */
263	movq	%rax,TF_RAX(%rsp)	/* syscall number */
264	movq	%rbx,TF_RBX(%rsp)	/* C preserved */
265	movq	%rbp,TF_RBP(%rsp)	/* C preserved */
266	movq	%r12,TF_R12(%rsp)	/* C preserved */
267	movq	%r13,TF_R13(%rsp)	/* C preserved */
268	movq	%r14,TF_R14(%rsp)	/* C preserved */
269	movq	%r15,TF_R15(%rsp)	/* C preserved */
270	FAKE_MCOUNT(TF_RIP(%rsp))
271	movq	%rsp, %rdi
272	call	syscall
273	movq	PCPU(CURPCB),%rax
274	testq	$PCB_FULLCTX,PCB_FLAGS(%rax)
275	jne	3f
2761:	/* Check for and handle AST's on return to userland */
277	cli
278	movq	PCPU(CURTHREAD),%rax
279	testl	$TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%rax)
280	je	2f
281	sti
282	movq	%rsp, %rdi
283	call	ast
284	jmp	1b
2852:	/* restore preserved registers */
286	MEXITCOUNT
287	movq	TF_RDI(%rsp),%rdi	/* bonus; preserve arg 1 */
288	movq	TF_RSI(%rsp),%rsi	/* bonus: preserve arg 2 */
289	movq	TF_RDX(%rsp),%rdx	/* return value 2 */
290	movq	TF_RAX(%rsp),%rax	/* return value 1 */
291	movq	TF_RBX(%rsp),%rbx	/* C preserved */
292	movq	TF_RBP(%rsp),%rbp	/* C preserved */
293	movq	TF_R12(%rsp),%r12	/* C preserved */
294	movq	TF_R13(%rsp),%r13	/* C preserved */
295	movq	TF_R14(%rsp),%r14	/* C preserved */
296	movq	TF_R15(%rsp),%r15	/* C preserved */
297	movq	TF_RFLAGS(%rsp),%r11	/* original %rflags */
298	movq	TF_RIP(%rsp),%rcx	/* original %rip */
299	movq	TF_RSP(%rsp),%r9	/* user stack pointer */
300	movq	%r9,%rsp		/* original %rsp */
301	swapgs
302	sysretq
3033:	/* Requested full context restore, use doreti for that */
304	andq	$~PCB_FULLCTX,PCB_FLAGS(%rax)
305	MEXITCOUNT
306	jmp	doreti
307
308/*
309 * Here for CYA insurance, in case a "syscall" instruction gets
310 * issued from 32 bit compatability mode. MSR_CSTAR has to point
311 * to *something* if EFER_SCE is enabled.
312 */
313IDTVEC(fast_syscall32)
314	sysret
315
316/*
317 * NMI handling is special.
318 *
319 * First, NMIs do not respect the state of the processor's RFLAGS.IF
320 * bit and the NMI handler may be invoked at any time, including when
321 * the processor is in a critical section with RFLAGS.IF == 0.  In
322 * particular, this means that the processor's GS.base values could be
323 * inconsistent on entry to the handler, and so we need to read
324 * MSR_GSBASE to determine if a 'swapgs' is needed.  We use '%ebx', a
325 * C-preserved register, to remember whether to swap GS back on the
326 * exit path.
327 *
328 * Second, the processor treats NMIs specially, blocking further NMIs
329 * until an 'iretq' instruction is executed.  We therefore need to
330 * execute the NMI handler with interrupts disabled to prevent a
331 * nested interrupt from executing an 'iretq' instruction and
332 * inadvertently taking the processor out of NMI mode.
333 */
334
335IDTVEC(nmi)
336	subq	$TF_RIP,%rsp
337	movq	$(T_NMI),TF_TRAPNO(%rsp)
338	movq	$0,TF_ADDR(%rsp)
339	movq	$0,TF_ERR(%rsp)
340	movq	%rdi,TF_RDI(%rsp)
341	movq	%rsi,TF_RSI(%rsp)
342	movq	%rdx,TF_RDX(%rsp)
343	movq	%rcx,TF_RCX(%rsp)
344	movq	%r8,TF_R8(%rsp)
345	movq	%r9,TF_R9(%rsp)
346	movq	%rax,TF_RAX(%rsp)
347	movq	%rbx,TF_RBX(%rsp)
348	movq	%rbp,TF_RBP(%rsp)
349	movq	%r10,TF_R10(%rsp)
350	movq	%r11,TF_R11(%rsp)
351	movq	%r12,TF_R12(%rsp)
352	movq	%r13,TF_R13(%rsp)
353	movq	%r14,TF_R14(%rsp)
354	movq	%r15,TF_R15(%rsp)
355	xorl	%ebx,%ebx
356	testb	$SEL_RPL_MASK,TF_CS(%rsp)
357	jnz	nmi_needswapgs		/* we came from userland */
358	movl	$MSR_GSBASE,%ecx
359	rdmsr
360	cmpl	$VM_MAXUSER_ADDRESS >> 32,%edx
361	jae	nmi_calltrap		/* GS.base holds a kernel VA */
362nmi_needswapgs:
363	incl	%ebx
364	swapgs
365/* Note: this label is also used by ddb and gdb: */
366nmi_calltrap:
367	FAKE_MCOUNT(TF_RIP(%rsp))
368	movq	%rsp, %rdi
369	call	trap
370	MEXITCOUNT
371	testl	%ebx,%ebx
372	jz	nmi_restoreregs
373	swapgs
374nmi_restoreregs:
375	movq	TF_RDI(%rsp),%rdi
376	movq	TF_RSI(%rsp),%rsi
377	movq	TF_RDX(%rsp),%rdx
378	movq	TF_RCX(%rsp),%rcx
379	movq	TF_R8(%rsp),%r8
380	movq	TF_R9(%rsp),%r9
381	movq	TF_RAX(%rsp),%rax
382	movq	TF_RBX(%rsp),%rbx
383	movq	TF_RBP(%rsp),%rbp
384	movq	TF_R10(%rsp),%r10
385	movq	TF_R11(%rsp),%r11
386	movq	TF_R12(%rsp),%r12
387	movq	TF_R13(%rsp),%r13
388	movq	TF_R14(%rsp),%r14
389	movq	TF_R15(%rsp),%r15
390	addq	$TF_RIP,%rsp
391	iretq
392
393ENTRY(fork_trampoline)
394	movq	%r12, %rdi		/* function */
395	movq	%rbx, %rsi		/* arg1 */
396	movq	%rsp, %rdx		/* trapframe pointer */
397	call	fork_exit
398	MEXITCOUNT
399	jmp	doreti			/* Handle any ASTs */
400
401/*
402 * To efficiently implement classification of trap and interrupt handlers
403 * for profiling, there must be only trap handlers between the labels btrap
404 * and bintr, and only interrupt handlers between the labels bintr and
405 * eintr.  This is implemented (partly) by including files that contain
406 * some of the handlers.  Before including the files, set up a normal asm
407 * environment so that the included files doen't need to know that they are
408 * included.
409 */
410
411#ifdef COMPAT_IA32
412	.data
413	.p2align 4
414	.text
415	SUPERALIGN_TEXT
416
417#include <amd64/ia32/ia32_exception.S>
418#endif
419
420	.data
421	.p2align 4
422	.text
423	SUPERALIGN_TEXT
424MCOUNT_LABEL(bintr)
425
426#include <amd64/amd64/apic_vector.S>
427
428#ifdef DEV_ATPIC
429	.data
430	.p2align 4
431	.text
432	SUPERALIGN_TEXT
433
434#include <amd64/isa/atpic_vector.S>
435#endif
436
437	.text
438MCOUNT_LABEL(eintr)
439
440/*
441 * void doreti(struct trapframe)
442 *
443 * Handle return from interrupts, traps and syscalls.
444 */
445	.text
446	SUPERALIGN_TEXT
447	.type	doreti,@function
448doreti:
449	FAKE_MCOUNT($bintr)		/* init "from" bintr -> doreti */
450	/*
451	 * Check if ASTs can be handled now.
452	 */
453	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* are we returning to user mode? */
454	jz	doreti_exit		/* can't handle ASTs now if not */
455
456doreti_ast:
457	/*
458	 * Check for ASTs atomically with returning.  Disabling CPU
459	 * interrupts provides sufficient locking eve in the SMP case,
460	 * since we will be informed of any new ASTs by an IPI.
461	 */
462	cli
463	movq	PCPU(CURTHREAD),%rax
464	testl	$TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%rax)
465	je	doreti_exit
466	sti
467	movq	%rsp, %rdi			/* pass a pointer to the trapframe */
468	call	ast
469	jmp	doreti_ast
470
471	/*
472	 * doreti_exit:	pop registers, iret.
473	 *
474	 *	The segment register pop is a special case, since it may
475	 *	fault if (for example) a sigreturn specifies bad segment
476	 *	registers.  The fault is handled in trap.c.
477	 */
478doreti_exit:
479	MEXITCOUNT
480	movq	TF_RDI(%rsp),%rdi
481	movq	TF_RSI(%rsp),%rsi
482	movq	TF_RDX(%rsp),%rdx
483	movq	TF_RCX(%rsp),%rcx
484	movq	TF_R8(%rsp),%r8
485	movq	TF_R9(%rsp),%r9
486	movq	TF_RAX(%rsp),%rax
487	movq	TF_RBX(%rsp),%rbx
488	movq	TF_RBP(%rsp),%rbp
489	movq	TF_R10(%rsp),%r10
490	movq	TF_R11(%rsp),%r11
491	movq	TF_R12(%rsp),%r12
492	movq	TF_R13(%rsp),%r13
493	movq	TF_R14(%rsp),%r14
494	movq	TF_R15(%rsp),%r15
495	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
496	jz	1f			/* keep running with kernel GS.base */
497	cli
498	swapgs
4991:	addq	$TF_RIP,%rsp		/* skip over tf_err, tf_trapno */
500	.globl	doreti_iret
501doreti_iret:
502	iretq
503
504	/*
505	 * doreti_iret_fault.  Alternative return code for
506	 * the case where we get a fault in the doreti_exit code
507	 * above.  trap() (amd64/amd64/trap.c) catches this specific
508	 * case, sends the process a signal and continues in the
509	 * corresponding place in the code below.
510	 */
511	ALIGN_TEXT
512	.globl	doreti_iret_fault
513doreti_iret_fault:
514	subq	$TF_RIP,%rsp		/* space including tf_err, tf_trapno */
515	testb	$SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
516	jz	1f			/* already running with kernel GS.base */
517	swapgs
5181:	testl	$PSL_I,TF_RFLAGS(%rsp)
519	jz	2f
520	sti
5212:	movq	%rdi,TF_RDI(%rsp)
522	movq	%rsi,TF_RSI(%rsp)
523	movq	%rdx,TF_RDX(%rsp)
524	movq	%rcx,TF_RCX(%rsp)
525	movq	%r8,TF_R8(%rsp)
526	movq	%r9,TF_R9(%rsp)
527	movq	%rax,TF_RAX(%rsp)
528	movq	%rbx,TF_RBX(%rsp)
529	movq	%rbp,TF_RBP(%rsp)
530	movq	%r10,TF_R10(%rsp)
531	movq	%r11,TF_R11(%rsp)
532	movq	%r12,TF_R12(%rsp)
533	movq	%r13,TF_R13(%rsp)
534	movq	%r14,TF_R14(%rsp)
535	movq	%r15,TF_R15(%rsp)
536	movq	$T_PROTFLT,TF_TRAPNO(%rsp)
537	movq	$0,TF_ERR(%rsp)	/* XXX should be the error code */
538	movq	$0,TF_ADDR(%rsp)
539	FAKE_MCOUNT(TF_RIP(%rsp))
540	jmp	calltrap
541