1/*-
2 * Copyright (c) 1989, 1990 William F. Jolitz.
3 * Copyright (c) 1990 The Regents of the University of California.
4 * Copyright (c) 2007 The FreeBSD Foundation
5 * All rights reserved.
6 *
7 * Portions of this software were developed by A. Joseph Koshy under
8 * sponsorship from the FreeBSD Foundation and Google, Inc.
9 *
10 * Redistribution and use in source and binary forms, with or without
11 * modification, are permitted provided that the following conditions
12 * are met:
13 * 1. Redistributions of source code must retain the above copyright
14 *    notice, this list of conditions and the following disclaimer.
15 * 2. Redistributions in binary form must reproduce the above copyright
16 *    notice, this list of conditions and the following disclaimer in the
17 *    documentation and/or other materials provided with the distribution.
18 * 4. Neither the name of the University nor the names of its contributors
19 *    may be used to endorse or promote products derived from this software
20 *    without specific prior written permission.
21 *
22 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
23 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
24 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
25 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
26 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
27 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
28 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
29 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
30 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
31 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
32 * SUCH DAMAGE.
33 *
34 * $FreeBSD: releng/11.0/sys/i386/i386/exception.s 302982 2016-07-18 04:33:12Z kib $
35 */
36
37#include "opt_apic.h"
38#include "opt_atpic.h"
39#include "opt_hwpmc_hooks.h"
40#include "opt_npx.h"
41
42#include <machine/asmacros.h>
43#include <machine/psl.h>
44#include <machine/trap.h>
45
46#include "assym.s"
47
48#define	SEL_RPL_MASK	0x0003
49#define	GSEL_KPL	0x0020	/* GSEL(GCODE_SEL, SEL_KPL) */
50
51#ifdef KDTRACE_HOOKS
52	.bss
53	.globl	dtrace_invop_jump_addr
54	.align	4
55	.type	dtrace_invop_jump_addr, @object
56	.size	dtrace_invop_jump_addr, 4
57dtrace_invop_jump_addr:
58	.zero	4
59	.globl	dtrace_invop_calltrap_addr
60	.align	4
61	.type	dtrace_invop_calltrap_addr, @object
62	.size	dtrace_invop_calltrap_addr, 4
63dtrace_invop_calltrap_addr:
64	.zero	8
65#endif
66	.text
67#ifdef HWPMC_HOOKS
68	ENTRY(start_exceptions)
69#endif
70/*****************************************************************************/
71/* Trap handling                                                             */
72/*****************************************************************************/
73/*
74 * Trap and fault vector routines.
75 *
76 * Most traps are 'trap gates', SDT_SYS386TGT.  A trap gate pushes state on
77 * the stack that mostly looks like an interrupt, but does not disable
78 * interrupts.  A few of the traps we are use are interrupt gates,
79 * SDT_SYS386IGT, which are nearly the same thing except interrupts are
80 * disabled on entry.
81 *
82 * The cpu will push a certain amount of state onto the kernel stack for
83 * the current process.  The amount of state depends on the type of trap
84 * and whether the trap crossed rings or not.  See i386/include/frame.h.
85 * At the very least the current EFLAGS (status register, which includes
86 * the interrupt disable state prior to the trap), the code segment register,
87 * and the return instruction pointer are pushed by the cpu.  The cpu
88 * will also push an 'error' code for certain traps.  We push a dummy
89 * error code for those traps where the cpu doesn't in order to maintain
90 * a consistent frame.  We also push a contrived 'trap number'.
91 *
92 * The cpu does not push the general registers, we must do that, and we
93 * must restore them prior to calling 'iret'.  The cpu adjusts the %cs and
94 * %ss segment registers, but does not mess with %ds, %es, or %fs.  Thus we
95 * must load them with appropriate values for supervisor mode operation.
96 */
97
98MCOUNT_LABEL(user)
99MCOUNT_LABEL(btrap)
100
101#define	TRAP(a)		pushl $(a) ; jmp alltraps
102
103IDTVEC(div)
104	pushl $0; TRAP(T_DIVIDE)
105IDTVEC(dbg)
106	pushl $0; TRAP(T_TRCTRAP)
107IDTVEC(nmi)
108	pushl $0; TRAP(T_NMI)
109IDTVEC(bpt)
110	pushl $0; TRAP(T_BPTFLT)
111IDTVEC(dtrace_ret)
112	pushl $0; TRAP(T_DTRACE_RET)
113IDTVEC(ofl)
114	pushl $0; TRAP(T_OFLOW)
115IDTVEC(bnd)
116	pushl $0; TRAP(T_BOUND)
117#ifndef KDTRACE_HOOKS
118IDTVEC(ill)
119	pushl $0; TRAP(T_PRIVINFLT)
120#endif
121IDTVEC(dna)
122	pushl $0; TRAP(T_DNA)
123IDTVEC(fpusegm)
124	pushl $0; TRAP(T_FPOPFLT)
125IDTVEC(tss)
126	TRAP(T_TSSFLT)
127IDTVEC(missing)
128	TRAP(T_SEGNPFLT)
129IDTVEC(stk)
130	TRAP(T_STKFLT)
131IDTVEC(prot)
132	TRAP(T_PROTFLT)
133IDTVEC(page)
134	TRAP(T_PAGEFLT)
135IDTVEC(mchk)
136	pushl $0; TRAP(T_MCHK)
137IDTVEC(rsvd)
138	pushl $0; TRAP(T_RESERVED)
139IDTVEC(fpu)
140	pushl $0; TRAP(T_ARITHTRAP)
141IDTVEC(align)
142	TRAP(T_ALIGNFLT)
143IDTVEC(xmm)
144	pushl $0; TRAP(T_XMMFLT)
145
146	/*
147	 * All traps except ones for syscalls jump to alltraps.  If
148	 * interrupts were enabled when the trap occurred, then interrupts
149	 * are enabled now if the trap was through a trap gate, else
150	 * disabled if the trap was through an interrupt gate.  Note that
151	 * int0x80_syscall is a trap gate.   Interrupt gates are used by
152	 * page faults, non-maskable interrupts, debug and breakpoint
153	 * exceptions.
154	 */
155	SUPERALIGN_TEXT
156	.globl	alltraps
157	.type	alltraps,@function
158alltraps:
159	pushal
160	pushl	$0
161	movw	%ds,(%esp)
162	pushl	$0
163	movw	%es,(%esp)
164	pushl	$0
165	movw	%fs,(%esp)
166alltraps_with_regs_pushed:
167	SET_KERNEL_SREGS
168	cld
169	FAKE_MCOUNT(TF_EIP(%esp))
170calltrap:
171	pushl	%esp
172	call	trap
173	add	$4, %esp
174
175	/*
176	 * Return via doreti to handle ASTs.
177	 */
178	MEXITCOUNT
179	jmp	doreti
180
181/*
182 * Privileged instruction fault.
183 */
184#ifdef KDTRACE_HOOKS
185	SUPERALIGN_TEXT
186IDTVEC(ill)
187	/* Check if there is no DTrace hook registered. */
188	cmpl	$0,dtrace_invop_jump_addr
189	je	norm_ill
190
191	/* Check if this is a user fault. */
192	cmpl	$GSEL_KPL, 4(%esp)	/* Check the code segment. */
193
194	/* If so, just handle it as a normal trap. */
195	jne	norm_ill
196
197	/*
198	 * This is a kernel instruction fault that might have been caused
199	 * by a DTrace provider.
200	 */
201	pushal				/* Push all registers onto the stack. */
202
203	/*
204	 * Set our jump address for the jump back in the event that
205	 * the exception wasn't caused by DTrace at all.
206	 */
207	movl	$norm_ill, dtrace_invop_calltrap_addr
208
209	/* Jump to the code hooked in by DTrace. */
210	jmpl	*dtrace_invop_jump_addr
211
212	/*
213	 * Process the instruction fault in the normal way.
214	 */
215norm_ill:
216	pushl $0
217	TRAP(T_PRIVINFLT)
218#endif
219
220/*
221 * Call gate entry for syscalls (lcall 7,0).
222 * This is used by FreeBSD 1.x a.out executables and "old" NetBSD executables.
223 *
224 * The intersegment call has been set up to specify one dummy parameter.
225 * This leaves a place to put eflags so that the call frame can be
226 * converted to a trap frame. Note that the eflags is (semi-)bogusly
227 * pushed into (what will be) tf_err and then copied later into the
228 * final spot. It has to be done this way because esp can't be just
229 * temporarily altered for the pushfl - an interrupt might come in
230 * and clobber the saved cs/eip.
231 */
232	SUPERALIGN_TEXT
233IDTVEC(lcall_syscall)
234	pushfl				/* save eflags */
235	popl	8(%esp)			/* shuffle into tf_eflags */
236	pushl	$7			/* sizeof "lcall 7,0" */
237	pushl	$0			/* tf_trapno */
238	pushal
239	pushl	$0
240	movw	%ds,(%esp)
241	pushl	$0
242	movw	%es,(%esp)
243	pushl	$0
244	movw	%fs,(%esp)
245	SET_KERNEL_SREGS
246	cld
247	FAKE_MCOUNT(TF_EIP(%esp))
248	pushl	%esp
249	call	syscall
250	add	$4, %esp
251	MEXITCOUNT
252	jmp	doreti
253
254/*
255 * Trap gate entry for syscalls (int 0x80).
256 * This is used by FreeBSD ELF executables, "new" NetBSD executables, and all
257 * Linux executables.
258 *
259 * Even though the name says 'int0x80', this is actually a trap gate, not an
260 * interrupt gate.  Thus interrupts are enabled on entry just as they are for
261 * a normal syscall.
262 */
263	SUPERALIGN_TEXT
264IDTVEC(int0x80_syscall)
265	pushl	$2			/* sizeof "int 0x80" */
266	pushl	$0			/* tf_trapno */
267	pushal
268	pushl	$0
269	movw	%ds,(%esp)
270	pushl	$0
271	movw	%es,(%esp)
272	pushl	$0
273	movw	%fs,(%esp)
274	SET_KERNEL_SREGS
275	cld
276	FAKE_MCOUNT(TF_EIP(%esp))
277	pushl	%esp
278	call	syscall
279	add	$4, %esp
280	MEXITCOUNT
281	jmp	doreti
282
283ENTRY(fork_trampoline)
284	pushl	%esp			/* trapframe pointer */
285	pushl	%ebx			/* arg1 */
286	pushl	%esi			/* function */
287	call	fork_exit
288	addl	$12,%esp
289	/* cut from syscall */
290
291	/*
292	 * Return via doreti to handle ASTs.
293	 */
294	MEXITCOUNT
295	jmp	doreti
296
297
298/*
299 * To efficiently implement classification of trap and interrupt handlers
300 * for profiling, there must be only trap handlers between the labels btrap
301 * and bintr, and only interrupt handlers between the labels bintr and
302 * eintr.  This is implemented (partly) by including files that contain
303 * some of the handlers.  Before including the files, set up a normal asm
304 * environment so that the included files doen't need to know that they are
305 * included.
306 */
307
308	.data
309	.p2align 4
310	.text
311	SUPERALIGN_TEXT
312MCOUNT_LABEL(bintr)
313
314#ifdef DEV_ATPIC
315#include <i386/i386/atpic_vector.s>
316#endif
317
318#if defined(DEV_APIC) && defined(DEV_ATPIC)
319	.data
320	.p2align 4
321	.text
322	SUPERALIGN_TEXT
323#endif
324
325#ifdef DEV_APIC
326#include <i386/i386/apic_vector.s>
327#endif
328
329	.data
330	.p2align 4
331	.text
332	SUPERALIGN_TEXT
333#include <i386/i386/vm86bios.s>
334
335	.text
336MCOUNT_LABEL(eintr)
337
338/*
339 * void doreti(struct trapframe)
340 *
341 * Handle return from interrupts, traps and syscalls.
342 */
343	.text
344	SUPERALIGN_TEXT
345	.type	doreti,@function
346	.globl	doreti
347doreti:
348	FAKE_MCOUNT($bintr)		/* init "from" bintr -> doreti */
349doreti_next:
350	/*
351	 * Check if ASTs can be handled now.  ASTs cannot be safely
352	 * processed when returning from an NMI.
353	 */
354	cmpb	$T_NMI,TF_TRAPNO(%esp)
355#ifdef HWPMC_HOOKS
356	je	doreti_nmi
357#else
358	je	doreti_exit
359#endif
360	/*
361	 * PSL_VM must be checked first since segment registers only
362	 * have an RPL in non-VM86 mode.
363	 * ASTs can not be handled now if we are in a vm86 call.
364	 */
365	testl	$PSL_VM,TF_EFLAGS(%esp)
366	jz	doreti_notvm86
367	movl	PCPU(CURPCB),%ecx
368	testl	$PCB_VM86CALL,PCB_FLAGS(%ecx)
369	jz	doreti_ast
370	jmp	doreti_exit
371
372doreti_notvm86:
373	testb	$SEL_RPL_MASK,TF_CS(%esp) /* are we returning to user mode? */
374	jz	doreti_exit		/* can't handle ASTs now if not */
375
376doreti_ast:
377	/*
378	 * Check for ASTs atomically with returning.  Disabling CPU
379	 * interrupts provides sufficient locking even in the SMP case,
380	 * since we will be informed of any new ASTs by an IPI.
381	 */
382	cli
383	movl	PCPU(CURTHREAD),%eax
384	testl	$TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%eax)
385	je	doreti_exit
386	sti
387	pushl	%esp			/* pass a pointer to the trapframe */
388	call	ast
389	add	$4,%esp
390	jmp	doreti_ast
391
392	/*
393	 * doreti_exit:	pop registers, iret.
394	 *
395	 *	The segment register pop is a special case, since it may
396	 *	fault if (for example) a sigreturn specifies bad segment
397	 *	registers.  The fault is handled in trap.c.
398	 */
399doreti_exit:
400	MEXITCOUNT
401
402	.globl	doreti_popl_fs
403doreti_popl_fs:
404	popl	%fs
405	.globl	doreti_popl_es
406doreti_popl_es:
407	popl	%es
408	.globl	doreti_popl_ds
409doreti_popl_ds:
410	popl	%ds
411	popal
412	addl	$8,%esp
413	.globl	doreti_iret
414doreti_iret:
415	iret
416
417	/*
418	 * doreti_iret_fault and friends.  Alternative return code for
419	 * the case where we get a fault in the doreti_exit code
420	 * above.  trap() (i386/i386/trap.c) catches this specific
421	 * case, sends the process a signal and continues in the
422	 * corresponding place in the code below.
423	 */
424	ALIGN_TEXT
425	.globl	doreti_iret_fault
426doreti_iret_fault:
427	subl	$8,%esp
428	pushal
429	pushl	$0
430	movw	%ds,(%esp)
431	.globl	doreti_popl_ds_fault
432doreti_popl_ds_fault:
433	pushl	$0
434	movw	%es,(%esp)
435	.globl	doreti_popl_es_fault
436doreti_popl_es_fault:
437	pushl	$0
438	movw	%fs,(%esp)
439	.globl	doreti_popl_fs_fault
440doreti_popl_fs_fault:
441	sti
442	movl	$0,TF_ERR(%esp)	/* XXX should be the error code */
443	movl	$T_PROTFLT,TF_TRAPNO(%esp)
444	jmp	alltraps_with_regs_pushed
445#ifdef HWPMC_HOOKS
446doreti_nmi:
447	/*
448	 * Since we are returning from an NMI, check if the current trap
449	 * was from user mode and if so whether the current thread
450	 * needs a user call chain capture.
451	 */
452	testb	$SEL_RPL_MASK,TF_CS(%esp)
453	jz	doreti_exit
454	movl	PCPU(CURTHREAD),%eax	/* curthread present? */
455	orl	%eax,%eax
456	jz	doreti_exit
457	testl	$TDP_CALLCHAIN,TD_PFLAGS(%eax) /* flagged for capture? */
458	jz	doreti_exit
459	/*
460	 * Take the processor out of NMI mode by executing a fake "iret".
461	 */
462	pushfl
463	pushl	%cs
464	pushl	$outofnmi
465	iret
466outofnmi:
467	/*
468	 * Call the callchain capture hook after turning interrupts back on.
469	 */
470	movl	pmc_hook,%ecx
471	orl	%ecx,%ecx
472	jz	doreti_exit
473	pushl	%esp			/* frame pointer */
474	pushl	$PMC_FN_USER_CALLCHAIN	/* command */
475	movl	PCPU(CURTHREAD),%eax
476	pushl	%eax			/* curthread */
477	sti
478	call	*%ecx
479	addl	$12,%esp
480	jmp	doreti_ast
481	ENTRY(end_exceptions)
482#endif
483