1757Sdg/*-
299703Sjulian * Copyright (c) 1989, 1990 William F. Jolitz.
3757Sdg * Copyright (c) 1990 The Regents of the University of California.
4174395Sjkoshy * Copyright (c) 2007 The FreeBSD Foundation
5757Sdg * All rights reserved.
6757Sdg *
7174395Sjkoshy * Portions of this software were developed by A. Joseph Koshy under
8174395Sjkoshy * sponsorship from the FreeBSD Foundation and Google, Inc.
9174395Sjkoshy *
10757Sdg * Redistribution and use in source and binary forms, with or without
11757Sdg * modification, are permitted provided that the following conditions
12757Sdg * are met:
13757Sdg * 1. Redistributions of source code must retain the above copyright
14757Sdg *    notice, this list of conditions and the following disclaimer.
15757Sdg * 2. Redistributions in binary form must reproduce the above copyright
16757Sdg *    notice, this list of conditions and the following disclaimer in the
17757Sdg *    documentation and/or other materials provided with the distribution.
18757Sdg * 4. Neither the name of the University nor the names of its contributors
19757Sdg *    may be used to endorse or promote products derived from this software
20757Sdg *    without specific prior written permission.
21757Sdg *
22757Sdg * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
23757Sdg * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
24757Sdg * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
25757Sdg * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
26757Sdg * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
27757Sdg * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
28757Sdg * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
29757Sdg * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
30757Sdg * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
31757Sdg * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
32757Sdg * SUCH DAMAGE.
33757Sdg *
3450477Speter * $FreeBSD$
35757Sdg */
36757Sdg
37129742Sbde#include "opt_apic.h"
38234144Sjhb#include "opt_atpic.h"
39174395Sjkoshy#include "opt_hwpmc_hooks.h"
40179277Sjb#include "opt_kdtrace.h"
4171257Speter#include "opt_npx.h"
4230265Speter
4328921Sfsmp#include <machine/asmacros.h>
4430786Sbde#include <machine/psl.h>
4530786Sbde#include <machine/trap.h>
46757Sdg
4730786Sbde#include "assym.s"
4830786Sbde
49757Sdg#define	SEL_RPL_MASK	0x0003
50179304Sattilio#define	GSEL_KPL	0x0020	/* GSEL(GCODE_SEL, SEL_KPL) */
51757Sdg
52179277Sjb#ifdef KDTRACE_HOOKS
53179277Sjb	.bss
54179277Sjb	.globl	dtrace_invop_jump_addr
55179277Sjb	.align	4
56179277Sjb	.type	dtrace_invop_jump_addr, @object
57252246Skib	.size	dtrace_invop_jump_addr, 4
58179277Sjbdtrace_invop_jump_addr:
59179277Sjb	.zero	4
60179277Sjb	.globl	dtrace_invop_calltrap_addr
61179277Sjb	.align	4
62179277Sjb	.type	dtrace_invop_calltrap_addr, @object
63252246Skib	.size	dtrace_invop_calltrap_addr, 4
64179277Sjbdtrace_invop_calltrap_addr:
65179277Sjb	.zero	8
66179277Sjb#endif
67757Sdg	.text
68174395Sjkoshy#ifdef HWPMC_HOOKS
69174395Sjkoshy	ENTRY(start_exceptions)
70174395Sjkoshy#endif
71757Sdg/*****************************************************************************/
72757Sdg/* Trap handling                                                             */
73757Sdg/*****************************************************************************/
74757Sdg/*
7558717Sdillon * Trap and fault vector routines.
7658717Sdillon *
7758717Sdillon * Most traps are 'trap gates', SDT_SYS386TGT.  A trap gate pushes state on
78252246Skib * the stack that mostly looks like an interrupt, but does not disable
79252246Skib * interrupts.  A few of the traps we are use are interrupt gates,
8058717Sdillon * SDT_SYS386IGT, which are nearly the same thing except interrupts are
8158717Sdillon * disabled on entry.
8258717Sdillon *
8358717Sdillon * The cpu will push a certain amount of state onto the kernel stack for
84252246Skib * the current process.  The amount of state depends on the type of trap
85252246Skib * and whether the trap crossed rings or not.  See i386/include/frame.h.
86252246Skib * At the very least the current EFLAGS (status register, which includes
8758717Sdillon * the interrupt disable state prior to the trap), the code segment register,
88252246Skib * and the return instruction pointer are pushed by the cpu.  The cpu
89252246Skib * will also push an 'error' code for certain traps.  We push a dummy
90252246Skib * error code for those traps where the cpu doesn't in order to maintain
9158717Sdillon * a consistent frame.  We also push a contrived 'trap number'.
9258717Sdillon *
93252246Skib * The cpu does not push the general registers, we must do that, and we
9458717Sdillon * must restore them prior to calling 'iret'.  The cpu adjusts the %cs and
9558717Sdillon * %ss segment registers, but does not mess with %ds, %es, or %fs.  Thus we
9658717Sdillon * must load them with appropriate values for supervisor mode operation.
971321Sdg */
981321Sdg
991321SdgMCOUNT_LABEL(user)
1001321SdgMCOUNT_LABEL(btrap)
1011321Sdg
102153135Sjhb#define	TRAP(a)		pushl $(a) ; jmp alltraps
103153135Sjhb
104757SdgIDTVEC(div)
105757Sdg	pushl $0; TRAP(T_DIVIDE)
106757SdgIDTVEC(dbg)
10781583Sbde	pushl $0; TRAP(T_TRCTRAP)
108147950SjkoshyIDTVEC(nmi)
109147950Sjkoshy	pushl $0; TRAP(T_NMI)
110757SdgIDTVEC(bpt)
11181583Sbde	pushl $0; TRAP(T_BPTFLT)
112211924SrpauloIDTVEC(dtrace_ret)
113211924Srpaulo	pushl $0; TRAP(T_DTRACE_RET)
114757SdgIDTVEC(ofl)
115757Sdg	pushl $0; TRAP(T_OFLOW)
116757SdgIDTVEC(bnd)
117757Sdg	pushl $0; TRAP(T_BOUND)
118179292Sbz#ifndef KDTRACE_HOOKS
119179292SbzIDTVEC(ill)
120179292Sbz	pushl $0; TRAP(T_PRIVINFLT)
121179292Sbz#endif
122757SdgIDTVEC(dna)
123757Sdg	pushl $0; TRAP(T_DNA)
124757SdgIDTVEC(fpusegm)
125757Sdg	pushl $0; TRAP(T_FPOPFLT)
126757SdgIDTVEC(tss)
127757Sdg	TRAP(T_TSSFLT)
128757SdgIDTVEC(missing)
129757Sdg	TRAP(T_SEGNPFLT)
130757SdgIDTVEC(stk)
131757Sdg	TRAP(T_STKFLT)
132757SdgIDTVEC(prot)
133757Sdg	TRAP(T_PROTFLT)
134757SdgIDTVEC(page)
135757Sdg	TRAP(T_PAGEFLT)
13617521SdgIDTVEC(mchk)
13717521Sdg	pushl $0; TRAP(T_MCHK)
138757SdgIDTVEC(rsvd)
139757Sdg	pushl $0; TRAP(T_RESERVED)
140757SdgIDTVEC(fpu)
141757Sdg	pushl $0; TRAP(T_ARITHTRAP)
1425603SbdeIDTVEC(align)
1435603Sbde	TRAP(T_ALIGNFLT)
14479609SpeterIDTVEC(xmm)
14579609Speter	pushl $0; TRAP(T_XMMFLT)
146139448Sjhb
14758717Sdillon	/*
148252246Skib	 * All traps except ones for syscalls jump to alltraps.  If
149252246Skib	 * interrupts were enabled when the trap occurred, then interrupts
150252246Skib	 * are enabled now if the trap was through a trap gate, else
151252246Skib	 * disabled if the trap was through an interrupt gate.  Note that
152252246Skib	 * int0x80_syscall is a trap gate.   Interrupt gates are used by
153252246Skib	 * page faults, non-maskable interrupts, debug and breakpoint
154157453Sjkoshy	 * exceptions.
15558717Sdillon	 */
156757Sdg	SUPERALIGN_TEXT
15773011Sjake	.globl	alltraps
15873011Sjake	.type	alltraps,@function
15973011Sjakealltraps:
160757Sdg	pushal
161757Sdg	pushl	%ds
162757Sdg	pushl	%es
16346129Sluoqi	pushl	%fs
1645603Sbdealltraps_with_regs_pushed:
165153135Sjhb	SET_KERNEL_SREGS
166209483Skib	cld
167129620Sbde	FAKE_MCOUNT(TF_EIP(%esp))
168757Sdgcalltrap:
169165302Skmacy	pushl	%esp
17073011Sjake	call	trap
171165302Skmacy	add	$4, %esp
172252246Skib
173757Sdg	/*
17473011Sjake	 * Return via doreti to handle ASTs.
175757Sdg	 */
1761321Sdg	MEXITCOUNT
17773011Sjake	jmp	doreti
178757Sdg
179757Sdg/*
180179277Sjb * Privileged instruction fault.
181179277Sjb */
182179292Sbz#ifdef KDTRACE_HOOKS
183179277Sjb	SUPERALIGN_TEXT
184179277SjbIDTVEC(ill)
185179277Sjb	/* Check if there is no DTrace hook registered. */
186179277Sjb	cmpl	$0,dtrace_invop_jump_addr
187179277Sjb	je	norm_ill
188179277Sjb
189179277Sjb	/* Check if this is a user fault. */
190179277Sjb	cmpl	$GSEL_KPL, 4(%esp)	/* Check the code segment. */
191252246Skib
192179277Sjb	/* If so, just handle it as a normal trap. */
193179277Sjb	jne	norm_ill
194252246Skib
195179277Sjb	/*
196179277Sjb	 * This is a kernel instruction fault that might have been caused
197179277Sjb	 * by a DTrace provider.
198179277Sjb	 */
199179277Sjb	pushal				/* Push all registers onto the stack. */
200179277Sjb
201179277Sjb	/*
202179277Sjb	 * Set our jump address for the jump back in the event that
203179277Sjb	 * the exception wasn't caused by DTrace at all.
204179277Sjb	 */
205179277Sjb	movl	$norm_ill, dtrace_invop_calltrap_addr
206179277Sjb
207179277Sjb	/* Jump to the code hooked in by DTrace. */
208179277Sjb	jmpl	*dtrace_invop_jump_addr
209179277Sjb
210179277Sjb	/*
211179277Sjb	 * Process the instruction fault in the normal way.
212179277Sjb	 */
213179277Sjbnorm_ill:
214179277Sjb	pushl $0
215179277Sjb	TRAP(T_PRIVINFLT)
216179292Sbz#endif
217179277Sjb
218179277Sjb/*
219252246Skib * Call gate entry for syscalls (lcall 7,0).
220252246Skib * This is used by FreeBSD 1.x a.out executables and "old" NetBSD executables.
22158717Sdillon *
22210609Sdg * The intersegment call has been set up to specify one dummy parameter.
22310609Sdg * This leaves a place to put eflags so that the call frame can be
22410609Sdg * converted to a trap frame. Note that the eflags is (semi-)bogusly
22510609Sdg * pushed into (what will be) tf_err and then copied later into the
22610609Sdg * final spot. It has to be done this way because esp can't be just
22710609Sdg * temporarily altered for the pushfl - an interrupt might come in
22810609Sdg * and clobber the saved cs/eip.
229757Sdg */
230757Sdg	SUPERALIGN_TEXT
23173001SjakeIDTVEC(lcall_syscall)
23273001Sjake	pushfl				/* save eflags */
23373001Sjake	popl	8(%esp)			/* shuffle into tf_eflags */
23473001Sjake	pushl	$7			/* sizeof "lcall 7,0" */
235100781Speter	subl	$4,%esp			/* skip over tf_trapno */
236100781Speter	pushal
237100781Speter	pushl	%ds
238100781Speter	pushl	%es
239100781Speter	pushl	%fs
240153135Sjhb	SET_KERNEL_SREGS
241209483Skib	cld
242129620Sbde	FAKE_MCOUNT(TF_EIP(%esp))
243165302Skmacy	pushl	%esp
244100781Speter	call	syscall
245165302Skmacy	add	$4, %esp
246100781Speter	MEXITCOUNT
247100781Speter	jmp	doreti
248757Sdg
249757Sdg/*
250252246Skib * Trap gate entry for syscalls (int 0x80).
251252246Skib * This is used by FreeBSD ELF executables, "new" NetBSD executables, and all
252252246Skib * Linux executables.
25358717Sdillon *
254252246Skib * Even though the name says 'int0x80', this is actually a trap gate, not an
255252246Skib * interrupt gate.  Thus interrupts are enabled on entry just as they are for
256252246Skib * a normal syscall.
2576380Ssos */
2586380Ssos	SUPERALIGN_TEXT
25914331SpeterIDTVEC(int0x80_syscall)
26073001Sjake	pushl	$2			/* sizeof "int 0x80" */
26173001Sjake	subl	$4,%esp			/* skip over tf_trapno */
2626380Ssos	pushal
2636380Ssos	pushl	%ds
2646380Ssos	pushl	%es
26546129Sluoqi	pushl	%fs
266153135Sjhb	SET_KERNEL_SREGS
267209483Skib	cld
268129620Sbde	FAKE_MCOUNT(TF_EIP(%esp))
269165302Skmacy	pushl	%esp
27073011Sjake	call	syscall
271165302Skmacy	add	$4, %esp
27258717Sdillon	MEXITCOUNT
27373011Sjake	jmp	doreti
2746380Ssos
27524691SpeterENTRY(fork_trampoline)
27671604Sjhb	pushl	%esp			/* trapframe pointer */
27728043Sfsmp	pushl	%ebx			/* arg1 */
27871522Sjhb	pushl	%esi			/* function */
27973011Sjake	call	fork_exit
28071604Sjhb	addl	$12,%esp
28124691Speter	/* cut from syscall */
28228641Sfsmp
28324691Speter	/*
28473011Sjake	 * Return via doreti to handle ASTs.
28524691Speter	 */
28624691Speter	MEXITCOUNT
28773011Sjake	jmp	doreti
28824691Speter
28928641Sfsmp
2906380Ssos/*
291129742Sbde * To efficiently implement classification of trap and interrupt handlers
292129742Sbde * for profiling, there must be only trap handlers between the labels btrap
293129742Sbde * and bintr, and only interrupt handlers between the labels bintr and
294129742Sbde * eintr.  This is implemented (partly) by including files that contain
295129742Sbde * some of the handlers.  Before including the files, set up a normal asm
296129742Sbde * environment so that the included files doen't need to know that they are
297129742Sbde * included.
29834840Sjlemon */
29934840Sjlemon
30099703Sjulian	.data
301129742Sbde	.p2align 4
302129742Sbde	.text
303129742Sbde	SUPERALIGN_TEXT
304129742SbdeMCOUNT_LABEL(bintr)
30599703Sjulian
306234144Sjhb#ifdef DEV_ATPIC
307204309Sattilio#include <i386/i386/atpic_vector.s>
308234144Sjhb#endif
309129742Sbde
310234144Sjhb#if defined(DEV_APIC) && defined(DEV_ATPIC)
311129742Sbde	.data
312129742Sbde	.p2align 4
313129742Sbde	.text
314129742Sbde	SUPERALIGN_TEXT
315234144Sjhb#endif
316129742Sbde
317234144Sjhb#ifdef DEV_APIC
318129742Sbde#include <i386/i386/apic_vector.s>
319129742Sbde#endif
320129742Sbde
321129742Sbde	.data
322129742Sbde	.p2align 4
323129742Sbde	.text
324129742Sbde	SUPERALIGN_TEXT
325129742Sbde#include <i386/i386/vm86bios.s>
326129742Sbde
327129742Sbde	.text
328129742SbdeMCOUNT_LABEL(eintr)
329129742Sbde
3303156Sbde/*
33199703Sjulian * void doreti(struct trapframe)
33299703Sjulian *
33399703Sjulian * Handle return from interrupts, traps and syscalls.
3343156Sbde */
3353156Sbde	.text
3363156Sbde	SUPERALIGN_TEXT
33799703Sjulian	.type	doreti,@function
33899703Sjuliandoreti:
339129624Sbde	FAKE_MCOUNT($bintr)		/* init "from" bintr -> doreti */
34099703Sjuliandoreti_next:
34199703Sjulian	/*
342174395Sjkoshy	 * Check if ASTs can be handled now.  ASTs cannot be safely
343174395Sjkoshy	 * processed when returning from an NMI.
34499703Sjulian	 */
345174395Sjkoshy	cmpb	$T_NMI,TF_TRAPNO(%esp)
346174395Sjkoshy#ifdef HWPMC_HOOKS
347174395Sjkoshy	je	doreti_nmi
348174395Sjkoshy#else
349174395Sjkoshy	je	doreti_exit
350174395Sjkoshy#endif
351174395Sjkoshy	/*
352174395Sjkoshy	 * PSL_VM must be checked first since segment registers only
353174395Sjkoshy	 * have an RPL in non-VM86 mode.
354252246Skib	 * ASTs can not be handled now if we are in a vm86 call.
355174395Sjkoshy	 */
356252246Skib	testl	$PSL_VM,TF_EFLAGS(%esp)
35799703Sjulian	jz	doreti_notvm86
358106542Sdavidxu	movl	PCPU(CURPCB),%ecx
359252246Skib	testl	$PCB_VM86CALL,PCB_FLAGS(%ecx)
360252246Skib	jz	doreti_ast
361252246Skib	jmp	doreti_exit
36299703Sjulian
36399703Sjuliandoreti_notvm86:
36499746Sjulian	testb	$SEL_RPL_MASK,TF_CS(%esp) /* are we returning to user mode? */
36599703Sjulian	jz	doreti_exit		/* can't handle ASTs now if not */
36699703Sjulian
36799703Sjuliandoreti_ast:
36899703Sjulian	/*
36999703Sjulian	 * Check for ASTs atomically with returning.  Disabling CPU
370118839Sjhb	 * interrupts provides sufficient locking even in the SMP case,
37199703Sjulian	 * since we will be informed of any new ASTs by an IPI.
37299703Sjulian	 */
37399703Sjulian	cli
37499703Sjulian	movl	PCPU(CURTHREAD),%eax
375111032Sjulian	testl	$TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%eax)
37699703Sjulian	je	doreti_exit
37799703Sjulian	sti
37899703Sjulian	pushl	%esp			/* pass a pointer to the trapframe */
37999703Sjulian	call	ast
38099703Sjulian	add	$4,%esp
38199703Sjulian	jmp	doreti_ast
38299703Sjulian
38399703Sjulian	/*
38499703Sjulian	 * doreti_exit:	pop registers, iret.
38599703Sjulian	 *
38699703Sjulian	 *	The segment register pop is a special case, since it may
38799703Sjulian	 *	fault if (for example) a sigreturn specifies bad segment
38899703Sjulian	 *	registers.  The fault is handled in trap.c.
38999703Sjulian	 */
39099703Sjuliandoreti_exit:
39199703Sjulian	MEXITCOUNT
39299703Sjulian
39399703Sjulian	.globl	doreti_popl_fs
39499703Sjuliandoreti_popl_fs:
39599703Sjulian	popl	%fs
39699703Sjulian	.globl	doreti_popl_es
39799703Sjuliandoreti_popl_es:
39899703Sjulian	popl	%es
39999703Sjulian	.globl	doreti_popl_ds
40099703Sjuliandoreti_popl_ds:
40199703Sjulian	popl	%ds
40299703Sjulian	popal
40399703Sjulian	addl	$8,%esp
40499703Sjulian	.globl	doreti_iret
40599703Sjuliandoreti_iret:
40699703Sjulian	iret
40799703Sjulian
408252246Skib	/*
40999703Sjulian	 * doreti_iret_fault and friends.  Alternative return code for
41099703Sjulian	 * the case where we get a fault in the doreti_exit code
41199703Sjulian	 * above.  trap() (i386/i386/trap.c) catches this specific
41299703Sjulian	 * case, sends the process a signal and continues in the
41399703Sjulian	 * corresponding place in the code below.
41499703Sjulian	 */
41599703Sjulian	ALIGN_TEXT
41699703Sjulian	.globl	doreti_iret_fault
41799703Sjuliandoreti_iret_fault:
41899703Sjulian	subl	$8,%esp
41999703Sjulian	pushal
42099703Sjulian	pushl	%ds
42199703Sjulian	.globl	doreti_popl_ds_fault
42299703Sjuliandoreti_popl_ds_fault:
42399703Sjulian	pushl	%es
42499703Sjulian	.globl	doreti_popl_es_fault
42599703Sjuliandoreti_popl_es_fault:
42699703Sjulian	pushl	%fs
42799703Sjulian	.globl	doreti_popl_fs_fault
42899703Sjuliandoreti_popl_fs_fault:
429251286Skib	sti
43099703Sjulian	movl	$0,TF_ERR(%esp)	/* XXX should be the error code */
43199703Sjulian	movl	$T_PROTFLT,TF_TRAPNO(%esp)
43299703Sjulian	jmp	alltraps_with_regs_pushed
433174395Sjkoshy#ifdef HWPMC_HOOKS
434174395Sjkoshydoreti_nmi:
435174395Sjkoshy	/*
436174395Sjkoshy	 * Since we are returning from an NMI, check if the current trap
437174395Sjkoshy	 * was from user mode and if so whether the current thread
438174395Sjkoshy	 * needs a user call chain capture.
439174395Sjkoshy	 */
440174395Sjkoshy	testb	$SEL_RPL_MASK,TF_CS(%esp)
441174395Sjkoshy	jz	doreti_exit
442174395Sjkoshy	movl	PCPU(CURTHREAD),%eax	/* curthread present? */
443174395Sjkoshy	orl	%eax,%eax
444174395Sjkoshy	jz	doreti_exit
445174395Sjkoshy	testl	$TDP_CALLCHAIN,TD_PFLAGS(%eax) /* flagged for capture? */
446174395Sjkoshy	jz	doreti_exit
447174395Sjkoshy	/*
448174395Sjkoshy	 * Take the processor out of NMI mode by executing a fake "iret".
449174395Sjkoshy	 */
450174395Sjkoshy	pushfl
451174395Sjkoshy	pushl	%cs
452174395Sjkoshy	pushl	$outofnmi
453174395Sjkoshy	iret
454174395Sjkoshyoutofnmi:
455174395Sjkoshy	/*
456186037Sjkoshy	 * Call the callchain capture hook after turning interrupts back on.
457174395Sjkoshy	 */
458186037Sjkoshy	movl	pmc_hook,%ecx
459186037Sjkoshy	orl	%ecx,%ecx
460186037Sjkoshy	jz	doreti_exit
461186037Sjkoshy	pushl	%esp			/* frame pointer */
462186037Sjkoshy	pushl	$PMC_FN_USER_CALLCHAIN	/* command */
463186037Sjkoshy	movl	PCPU(CURTHREAD),%eax
464186037Sjkoshy	pushl	%eax			/* curthread */
465174395Sjkoshy	sti
466186037Sjkoshy	call	*%ecx
467186037Sjkoshy	addl	$12,%esp
468174395Sjkoshy	jmp	doreti_ast
469174395Sjkoshy	ENTRY(end_exceptions)
470174395Sjkoshy#endif
471