xref: /onnv-gate/usr/src/uts/intel/ia32/ml/exception.s (revision 0:68f95e015346)
1*0Sstevel@tonic-gate/*
2*0Sstevel@tonic-gate * Copyright 2005 Sun Microsystems, Inc.  All rights reserved.
3*0Sstevel@tonic-gate * Use is subject to license terms.
4*0Sstevel@tonic-gate */
5*0Sstevel@tonic-gate
6*0Sstevel@tonic-gate/*
7*0Sstevel@tonic-gate * Copyright (c) 1989, 1990 William F. Jolitz.
8*0Sstevel@tonic-gate * Copyright (c) 1990 The Regents of the University of California.
9*0Sstevel@tonic-gate * All rights reserved.
10*0Sstevel@tonic-gate *
11*0Sstevel@tonic-gate * Redistribution and use in source and binary forms, with or without
12*0Sstevel@tonic-gate * modification, are permitted provided that the following conditions
13*0Sstevel@tonic-gate * are met:
14*0Sstevel@tonic-gate * 1. Redistributions of source code must retain the above copyright
15*0Sstevel@tonic-gate *    notice, this list of conditions and the following disclaimer.
16*0Sstevel@tonic-gate * 2. Redistributions in binary form must reproduce the above copyright
17*0Sstevel@tonic-gate *    notice, this list of conditions and the following disclaimer in the
18*0Sstevel@tonic-gate *    documentation and/or other materials provided with the distribution.
19*0Sstevel@tonic-gate * 3. All advertising materials mentioning features or use of this software
20*0Sstevel@tonic-gate *    must display the following acknowledgement:
21*0Sstevel@tonic-gate *	This product includes software developed by the University of
22*0Sstevel@tonic-gate *	California, Berkeley and its contributors.
23*0Sstevel@tonic-gate * 4. Neither the name of the University nor the names of its contributors
24*0Sstevel@tonic-gate *    may be used to endorse or promote products derived from this software
25*0Sstevel@tonic-gate *    without specific prior written permission.
26*0Sstevel@tonic-gate *
27*0Sstevel@tonic-gate * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
28*0Sstevel@tonic-gate * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
29*0Sstevel@tonic-gate * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
30*0Sstevel@tonic-gate * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
31*0Sstevel@tonic-gate * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
32*0Sstevel@tonic-gate * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
33*0Sstevel@tonic-gate * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
34*0Sstevel@tonic-gate * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
35*0Sstevel@tonic-gate * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
36*0Sstevel@tonic-gate * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
37*0Sstevel@tonic-gate * SUCH DAMAGE.
38*0Sstevel@tonic-gate *
39*0Sstevel@tonic-gate * $FreeBSD: src/sys/amd64/amd64/exception.S,v 1.113 2003/10/15 02:04:52 peter Exp $
40*0Sstevel@tonic-gate */
41*0Sstevel@tonic-gate
42*0Sstevel@tonic-gate#pragma ident	"%Z%%M%	%I%	%E% SMI"
43*0Sstevel@tonic-gate
44*0Sstevel@tonic-gate#include <sys/asm_linkage.h>
45*0Sstevel@tonic-gate#include <sys/asm_misc.h>
46*0Sstevel@tonic-gate#include <sys/trap.h>
47*0Sstevel@tonic-gate#include <sys/psw.h>
48*0Sstevel@tonic-gate#include <sys/regset.h>
49*0Sstevel@tonic-gate#include <sys/privregs.h>
50*0Sstevel@tonic-gate#include <sys/dtrace.h>
51*0Sstevel@tonic-gate#include <sys/traptrace.h>
52*0Sstevel@tonic-gate
53*0Sstevel@tonic-gate/*
54*0Sstevel@tonic-gate * only one routine in this file is interesting to lint
55*0Sstevel@tonic-gate */
56*0Sstevel@tonic-gate
57*0Sstevel@tonic-gate#if defined(__lint)
58*0Sstevel@tonic-gate
59*0Sstevel@tonic-gatevoid
60*0Sstevel@tonic-gatendptrap_frstor(void)
61*0Sstevel@tonic-gate{}
62*0Sstevel@tonic-gate
63*0Sstevel@tonic-gate#else
64*0Sstevel@tonic-gate
65*0Sstevel@tonic-gate#include "assym.h"
66*0Sstevel@tonic-gate
67*0Sstevel@tonic-gate/*
68*0Sstevel@tonic-gate * push $0 on stack for traps that do not
69*0Sstevel@tonic-gate * generate an error code. This is so the rest
70*0Sstevel@tonic-gate * of the kernel can expect a consistent stack
71*0Sstevel@tonic-gate * from from any exception.
72*0Sstevel@tonic-gate */
73*0Sstevel@tonic-gate#define	TRAP_NOERR(trapno)	\
74*0Sstevel@tonic-gate	push	$0;		\
75*0Sstevel@tonic-gate	push	$trapno
76*0Sstevel@tonic-gate
77*0Sstevel@tonic-gate/*
78*0Sstevel@tonic-gate * error code already pushed by hw
79*0Sstevel@tonic-gate * onto stack.
80*0Sstevel@tonic-gate */
81*0Sstevel@tonic-gate#define	TRAP_ERR(trapno)	\
82*0Sstevel@tonic-gate	push	$trapno
83*0Sstevel@tonic-gate
84*0Sstevel@tonic-gate	/*
85*0Sstevel@tonic-gate	 * #DE
86*0Sstevel@tonic-gate	 */
87*0Sstevel@tonic-gate	ENTRY_NP(div0trap)
88*0Sstevel@tonic-gate	TRAP_NOERR(T_ZERODIV)	/* $0 */
89*0Sstevel@tonic-gate	jmp	cmntrap
90*0Sstevel@tonic-gate	SET_SIZE(div0trap)
91*0Sstevel@tonic-gate
92*0Sstevel@tonic-gate#if defined(__amd64)
93*0Sstevel@tonic-gate	/*
94*0Sstevel@tonic-gate	 * #DB
95*0Sstevel@tonic-gate	 *
96*0Sstevel@tonic-gate	 * If we get here as a result of single-stepping a sysenter
97*0Sstevel@tonic-gate	 * instruction, we suddenly find ourselves taking a #db
98*0Sstevel@tonic-gate	 * in kernel mode -before- we've swapgs'ed.  So before we can
99*0Sstevel@tonic-gate	 * take the trap, we do the swapgs here, and fix the return
100*0Sstevel@tonic-gate	 * %rip in trap() so that we return immediately after the
101*0Sstevel@tonic-gate	 * swapgs in the sysenter handler to avoid doing the swapgs again.
102*0Sstevel@tonic-gate	 *
103*0Sstevel@tonic-gate	 * Nobody said that the design of sysenter was particularly
104*0Sstevel@tonic-gate	 * elegant, did they?
105*0Sstevel@tonic-gate	 */
106*0Sstevel@tonic-gate	ENTRY_NP(dbgtrap)
107*0Sstevel@tonic-gate	pushq	%r11
108*0Sstevel@tonic-gate	leaq	sys_sysenter(%rip), %r11
109*0Sstevel@tonic-gate	cmpq	%r11, 8(%rsp)
110*0Sstevel@tonic-gate	jne	1f
111*0Sstevel@tonic-gate	swapgs
112*0Sstevel@tonic-gate1:	popq	%r11
113*0Sstevel@tonic-gate	TRAP_NOERR(T_SGLSTP)	/* $1 */
114*0Sstevel@tonic-gate	jmp	cmntrap
115*0Sstevel@tonic-gate	SET_SIZE(dbgtrap)
116*0Sstevel@tonic-gate
117*0Sstevel@tonic-gate#elif defined(__i386)
118*0Sstevel@tonic-gate	/*
119*0Sstevel@tonic-gate	 * #DB
120*0Sstevel@tonic-gate	 */
121*0Sstevel@tonic-gate	ENTRY_NP(dbgtrap)
122*0Sstevel@tonic-gate	TRAP_NOERR(T_SGLSTP)	/* $1 */
123*0Sstevel@tonic-gate	jmp	cmntrap
124*0Sstevel@tonic-gate	SET_SIZE(dbgtrap)
125*0Sstevel@tonic-gate#endif
126*0Sstevel@tonic-gate
127*0Sstevel@tonic-gate#if defined(__amd64)
128*0Sstevel@tonic-gate
129*0Sstevel@tonic-gate/*
130*0Sstevel@tonic-gate * Macro to set the gsbase or kgsbase to the address of the struct cpu
131*0Sstevel@tonic-gate * for this processor.  If we came from userland, set kgsbase else clear
132*0Sstevel@tonic-gate * gs and set gsbase.  We find the proper cpu struct by looping through
133*0Sstevel@tonic-gate * the cpu structs for all processors till we find a match for the gdt
134*0Sstevel@tonic-gate * of the trapping processor.  The stack is expected to be pointing at
135*0Sstevel@tonic-gate * The standard regs pushed by hardware on a trap (plus error code and trapno).
136*0Sstevel@tonic-gate */
137*0Sstevel@tonic-gate#define	SET_CPU_GSBASE							\
138*0Sstevel@tonic-gate	subq	$REGOFF_TRAPNO, %rsp;	/* save regs */			\
139*0Sstevel@tonic-gate	movq	%rax, REGOFF_RAX(%rsp);					\
140*0Sstevel@tonic-gate	movq	%rbx, REGOFF_RBX(%rsp);					\
141*0Sstevel@tonic-gate	movq	%rcx, REGOFF_RCX(%rsp);					\
142*0Sstevel@tonic-gate	movq	%rdx, REGOFF_RDX(%rsp);					\
143*0Sstevel@tonic-gate	movq	%rbp, REGOFF_RBP(%rsp);					\
144*0Sstevel@tonic-gate	movq	%rsp, %rbp;						\
145*0Sstevel@tonic-gate	subq	$16, %rsp;		/* space for gdt */		\
146*0Sstevel@tonic-gate	sgdt	6(%rsp);						\
147*0Sstevel@tonic-gate	movq	8(%rsp), %rcx;		/* %rcx has gdt to match */	\
148*0Sstevel@tonic-gate	xorl	%ebx, %ebx;		/* loop index */		\
149*0Sstevel@tonic-gate	leaq	cpu(%rip), %rdx;	/* cpu pointer array */		\
150*0Sstevel@tonic-gate1:									\
151*0Sstevel@tonic-gate	movq	(%rdx, %rbx, CLONGSIZE), %rax;	/* get cpu[i] */	\
152*0Sstevel@tonic-gate	cmpq	$0x0, %rax;		/* cpu[i] == NULL ? */		\
153*0Sstevel@tonic-gate	je	2f;			/* yes, continue */		\
154*0Sstevel@tonic-gate	cmpq	%rcx, CPU_GDT(%rax);	/* gdt == cpu[i]->cpu_gdt ? */	\
155*0Sstevel@tonic-gate	je	3f;			/* yes, go set gsbase */	\
156*0Sstevel@tonic-gate2:									\
157*0Sstevel@tonic-gate	incl	%ebx;			/* i++ */			\
158*0Sstevel@tonic-gate	cmpl	$NCPU, %ebx;		/* i < NCPU ? */		\
159*0Sstevel@tonic-gate	jb	1b;			/* yes, loop */			\
160*0Sstevel@tonic-gate/* XXX BIG trouble if we fall thru here.  We didn't find a gdt match */	\
161*0Sstevel@tonic-gate3:									\
162*0Sstevel@tonic-gate	movl	$MSR_AMD_KGSBASE, %ecx;					\
163*0Sstevel@tonic-gate	cmpw	$KCS_SEL, REGOFF_CS(%rbp); /* trap from kernel? */	\
164*0Sstevel@tonic-gate	jne	4f;			/* no, go set KGSBASE */	\
165*0Sstevel@tonic-gate	movl	$MSR_AMD_GSBASE, %ecx;	/* yes, set GSBASE */		\
166*0Sstevel@tonic-gate        mfence;				/* OPTERON_ERRATUM_88 */	\
167*0Sstevel@tonic-gate4:									\
168*0Sstevel@tonic-gate	movq	%rax, %rdx;		/* write base register */	\
169*0Sstevel@tonic-gate	shrq	$32, %rdx;						\
170*0Sstevel@tonic-gate	wrmsr;								\
171*0Sstevel@tonic-gate	movq	REGOFF_RDX(%rbp), %rdx;	/* restore regs */		\
172*0Sstevel@tonic-gate	movq	REGOFF_RCX(%rbp), %rcx;					\
173*0Sstevel@tonic-gate	movq	REGOFF_RBX(%rbp), %rbx;					\
174*0Sstevel@tonic-gate	movq	REGOFF_RAX(%rbp), %rax;					\
175*0Sstevel@tonic-gate	movq	%rbp, %rsp;						\
176*0Sstevel@tonic-gate	movq	REGOFF_RBP(%rsp), %rbp;					\
177*0Sstevel@tonic-gate	addq	$REGOFF_TRAPNO, %rsp	/* pop stack */
178*0Sstevel@tonic-gate#endif	/* __amd64 */
179*0Sstevel@tonic-gate
180*0Sstevel@tonic-gate
181*0Sstevel@tonic-gate
182*0Sstevel@tonic-gate
183*0Sstevel@tonic-gate	.globl	nmivect
184*0Sstevel@tonic-gate	.globl	idt0_default_r
185*0Sstevel@tonic-gate
186*0Sstevel@tonic-gate#if defined(__amd64)
187*0Sstevel@tonic-gate
188*0Sstevel@tonic-gate	/*
189*0Sstevel@tonic-gate	 * #NMI
190*0Sstevel@tonic-gate	 */
191*0Sstevel@tonic-gate	ENTRY_NP(nmiint)
192*0Sstevel@tonic-gate	TRAP_NOERR(T_NMIFLT)	/* $2 */
193*0Sstevel@tonic-gate
194*0Sstevel@tonic-gate	SET_CPU_GSBASE
195*0Sstevel@tonic-gate
196*0Sstevel@tonic-gate	/*
197*0Sstevel@tonic-gate	 * Save all registers and setup segment registers
198*0Sstevel@tonic-gate	 * with kernel selectors.
199*0Sstevel@tonic-gate	 */
200*0Sstevel@tonic-gate	INTR_PUSH
201*0Sstevel@tonic-gate
202*0Sstevel@tonic-gate	DISABLE_INTR_FLAGS		/* and set the kernel flags */
203*0Sstevel@tonic-gate
204*0Sstevel@tonic-gate	TRACE_PTR(%r12, %rax, %eax, %rdx, $TT_TRAP)
205*0Sstevel@tonic-gate
206*0Sstevel@tonic-gate	TRACE_REGS(%r12, %rsp, %rax, %rbx)
207*0Sstevel@tonic-gate	TRACE_STAMP(%r12)
208*0Sstevel@tonic-gate
209*0Sstevel@tonic-gate	movq	%rsp, %rbp
210*0Sstevel@tonic-gate
211*0Sstevel@tonic-gate	movq	%rbp, %rdi
212*0Sstevel@tonic-gate	call	av_dispatch_nmivect
213*0Sstevel@tonic-gate
214*0Sstevel@tonic-gate	INTR_POP
215*0Sstevel@tonic-gate	iretq
216*0Sstevel@tonic-gate	SET_SIZE(nmiint)
217*0Sstevel@tonic-gate
218*0Sstevel@tonic-gate#elif defined(__i386)
219*0Sstevel@tonic-gate
220*0Sstevel@tonic-gate	/*
221*0Sstevel@tonic-gate	 * #NMI
222*0Sstevel@tonic-gate	 */
223*0Sstevel@tonic-gate	ENTRY_NP(nmiint)
224*0Sstevel@tonic-gate	TRAP_NOERR(T_NMIFLT)	/* $2 */
225*0Sstevel@tonic-gate
226*0Sstevel@tonic-gate	/*
227*0Sstevel@tonic-gate	 * Save all registers and setup segment registers
228*0Sstevel@tonic-gate	 * with kernel selectors.
229*0Sstevel@tonic-gate	 */
230*0Sstevel@tonic-gate	INTR_PUSH
231*0Sstevel@tonic-gate
232*0Sstevel@tonic-gate	/*
233*0Sstevel@tonic-gate	 * setup pointer to reg struct as 2nd argument.
234*0Sstevel@tonic-gate	 */
235*0Sstevel@tonic-gate	movl	%esp, %ebp
236*0Sstevel@tonic-gate	pushl	%ebp
237*0Sstevel@tonic-gate
238*0Sstevel@tonic-gate	DISABLE_INTR_FLAGS
239*0Sstevel@tonic-gate
240*0Sstevel@tonic-gate	movl	nmivect, %esi		/* get autovect structure */
241*0Sstevel@tonic-gateloop1:
242*0Sstevel@tonic-gate	cmpl	$0, %esi		/* if pointer is null  */
243*0Sstevel@tonic-gate	je	.intr_ret		/* 	we're done */
244*0Sstevel@tonic-gate	movl	AV_VECTOR(%esi), %edx	/* get the interrupt routine */
245*0Sstevel@tonic-gate	pushl	AV_INTARG1(%esi)	/* get argument to interrupt routine */
246*0Sstevel@tonic-gate	call	*%edx			/* call interrupt routine with arg */
247*0Sstevel@tonic-gate	addl	$4, %esp
248*0Sstevel@tonic-gate	movl	AV_LINK(%esi), %esi	/* get next routine on list */
249*0Sstevel@tonic-gate	jmp	loop1			/* keep looping until end of list */
250*0Sstevel@tonic-gate
251*0Sstevel@tonic-gate.intr_ret:
252*0Sstevel@tonic-gate	addl	$4, %esp		/* 'pop' %ebp */
253*0Sstevel@tonic-gate	INTR_POP_USER
254*0Sstevel@tonic-gate	iret
255*0Sstevel@tonic-gate	SET_SIZE(nmiint)
256*0Sstevel@tonic-gate
257*0Sstevel@tonic-gate#endif	/* __i386 */
258*0Sstevel@tonic-gate
259*0Sstevel@tonic-gate	/*
260*0Sstevel@tonic-gate	 * #BP
261*0Sstevel@tonic-gate	 */
262*0Sstevel@tonic-gate	ENTRY_NP(brktrap)
263*0Sstevel@tonic-gate#if defined(__amd64)
264*0Sstevel@tonic-gate	cmpw	$KCS_SEL, 8(%rsp)
265*0Sstevel@tonic-gate	je	bp_jmpud
266*0Sstevel@tonic-gate#endif
267*0Sstevel@tonic-gate
268*0Sstevel@tonic-gate	TRAP_NOERR(T_BPTFLT)	/* $3 */
269*0Sstevel@tonic-gate	jmp	dtrace_trap
270*0Sstevel@tonic-gate
271*0Sstevel@tonic-gate#if defined(__amd64)
272*0Sstevel@tonic-gatebp_jmpud:
273*0Sstevel@tonic-gate	/*
274*0Sstevel@tonic-gate	 * This is a breakpoint in the kernel -- it is very likely that this
275*0Sstevel@tonic-gate	 * is DTrace-induced.  To unify DTrace handling, we spoof this as an
276*0Sstevel@tonic-gate	 * invalid opcode (#UD) fault.  Note that #BP is a trap, not a fault --
277*0Sstevel@tonic-gate	 * we must decrement the trapping %rip to make it appear as a fault.
278*0Sstevel@tonic-gate	 * We then push a non-zero error code to indicate that this is coming
279*0Sstevel@tonic-gate	 * from #BP.
280*0Sstevel@tonic-gate	 */
281*0Sstevel@tonic-gate	decq	(%rsp)
282*0Sstevel@tonic-gate	push	$1			/* error code -- non-zero for #BP */
283*0Sstevel@tonic-gate	jmp	ud_kernel
284*0Sstevel@tonic-gate#endif
285*0Sstevel@tonic-gate
286*0Sstevel@tonic-gate	SET_SIZE(brktrap)
287*0Sstevel@tonic-gate
288*0Sstevel@tonic-gate	/*
289*0Sstevel@tonic-gate	 * #OF
290*0Sstevel@tonic-gate	 */
291*0Sstevel@tonic-gate	ENTRY_NP(ovflotrap)
292*0Sstevel@tonic-gate	TRAP_NOERR(T_OVFLW)	/* $4 */
293*0Sstevel@tonic-gate	jmp	cmntrap
294*0Sstevel@tonic-gate	SET_SIZE(ovflotrap)
295*0Sstevel@tonic-gate
296*0Sstevel@tonic-gate	/*
297*0Sstevel@tonic-gate	 * #BR
298*0Sstevel@tonic-gate	 */
299*0Sstevel@tonic-gate	ENTRY_NP(boundstrap)
300*0Sstevel@tonic-gate	TRAP_NOERR(T_BOUNDFLT)	/* $5 */
301*0Sstevel@tonic-gate	jmp	cmntrap
302*0Sstevel@tonic-gate	SET_SIZE(boundstrap)
303*0Sstevel@tonic-gate
304*0Sstevel@tonic-gate#if defined(__amd64)
305*0Sstevel@tonic-gate
306*0Sstevel@tonic-gate	ENTRY_NP(invoptrap)
307*0Sstevel@tonic-gate	cmpw	$KCS_SEL, 8(%rsp)
308*0Sstevel@tonic-gate	jne	ud_user
309*0Sstevel@tonic-gate
310*0Sstevel@tonic-gate	push	$0			/* error code -- zero for #UD */
311*0Sstevel@tonic-gateud_kernel:
312*0Sstevel@tonic-gate	push	$0xdddd			/* a dummy trap number */
313*0Sstevel@tonic-gate	TRAP_PUSH
314*0Sstevel@tonic-gate	movq	REGOFF_RIP(%rsp), %rdi
315*0Sstevel@tonic-gate	movq	REGOFF_RSP(%rsp), %rsi
316*0Sstevel@tonic-gate	movq	REGOFF_RAX(%rsp), %rdx
317*0Sstevel@tonic-gate	pushq	(%rsi)
318*0Sstevel@tonic-gate	movq	%rsp, %rsi
319*0Sstevel@tonic-gate	call	dtrace_invop
320*0Sstevel@tonic-gate	ALTENTRY(dtrace_invop_callsite)
321*0Sstevel@tonic-gate	addq	$8, %rsp
322*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_PUSHL_EBP, %eax
323*0Sstevel@tonic-gate	je	ud_push
324*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_LEAVE, %eax
325*0Sstevel@tonic-gate	je	ud_leave
326*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_NOP, %eax
327*0Sstevel@tonic-gate	je	ud_nop
328*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_RET, %eax
329*0Sstevel@tonic-gate	je	ud_ret
330*0Sstevel@tonic-gate	jmp	ud_trap
331*0Sstevel@tonic-gate
332*0Sstevel@tonic-gateud_push:
333*0Sstevel@tonic-gate	/*
334*0Sstevel@tonic-gate	 * We must emulate a "pushq %rbp".  To do this, we pull the stack
335*0Sstevel@tonic-gate	 * down 8 bytes, and then store the base pointer.
336*0Sstevel@tonic-gate	 */
337*0Sstevel@tonic-gate	INTR_POP
338*0Sstevel@tonic-gate	subq	$16, %rsp		/* make room for %rbp */
339*0Sstevel@tonic-gate	pushq	%rax			/* push temp */
340*0Sstevel@tonic-gate	movq	24(%rsp), %rax		/* load calling RIP */
341*0Sstevel@tonic-gate	addq	$1, %rax		/* increment over trapping instr */
342*0Sstevel@tonic-gate	movq	%rax, 8(%rsp)		/* store calling RIP */
343*0Sstevel@tonic-gate	movq	32(%rsp), %rax		/* load calling CS */
344*0Sstevel@tonic-gate	movq	%rax, 16(%rsp)		/* store calling CS */
345*0Sstevel@tonic-gate	movq	40(%rsp), %rax		/* load calling RFLAGS */
346*0Sstevel@tonic-gate	movq	%rax, 24(%rsp)		/* store calling RFLAGS */
347*0Sstevel@tonic-gate	movq	48(%rsp), %rax		/* load calling RSP */
348*0Sstevel@tonic-gate	subq	$8, %rax		/* make room for %rbp */
349*0Sstevel@tonic-gate	movq	%rax, 32(%rsp)		/* store calling RSP */
350*0Sstevel@tonic-gate	movq	56(%rsp), %rax		/* load calling SS */
351*0Sstevel@tonic-gate	movq	%rax, 40(%rsp)		/* store calling SS */
352*0Sstevel@tonic-gate	movq	32(%rsp), %rax		/* reload calling RSP */
353*0Sstevel@tonic-gate	movq	%rbp, (%rax)		/* store %rbp there */
354*0Sstevel@tonic-gate	popq	%rax			/* pop off temp */
355*0Sstevel@tonic-gate	iretq				/* return from interrupt */
356*0Sstevel@tonic-gate
357*0Sstevel@tonic-gateud_leave:
358*0Sstevel@tonic-gate	/*
359*0Sstevel@tonic-gate	 * We must emulate a "leave", which is the same as a "movq %rbp, %rsp"
360*0Sstevel@tonic-gate	 * followed by a "popq %rbp".  This is quite a bit simpler on amd64
361*0Sstevel@tonic-gate	 * than it is on i386 -- we can exploit the fact that the %rsp is
362*0Sstevel@tonic-gate	 * explicitly saved to effect the pop without having to reshuffle
363*0Sstevel@tonic-gate	 * the other data pushed for the trap.
364*0Sstevel@tonic-gate	 */
365*0Sstevel@tonic-gate	INTR_POP
366*0Sstevel@tonic-gate	pushq	%rax			/* push temp */
367*0Sstevel@tonic-gate	movq	8(%rsp), %rax		/* load calling RIP */
368*0Sstevel@tonic-gate	addq	$1, %rax		/* increment over trapping instr */
369*0Sstevel@tonic-gate	movq	%rax, 8(%rsp)		/* store calling RIP */
370*0Sstevel@tonic-gate	movq	(%rbp), %rax		/* get new %rbp */
371*0Sstevel@tonic-gate	addq	$8, %rbp		/* adjust new %rsp */
372*0Sstevel@tonic-gate	movq	%rbp, 32(%rsp)		/* store new %rsp */
373*0Sstevel@tonic-gate	movq	%rax, %rbp		/* set new %rbp */
374*0Sstevel@tonic-gate	popq	%rax			/* pop off temp */
375*0Sstevel@tonic-gate	iretq				/* return from interrupt */
376*0Sstevel@tonic-gate
377*0Sstevel@tonic-gateud_nop:
378*0Sstevel@tonic-gate	/*
379*0Sstevel@tonic-gate	 * We must emulate a "nop".  This is obviously not hard:  we need only
380*0Sstevel@tonic-gate	 * advance the %rip by one.
381*0Sstevel@tonic-gate	 */
382*0Sstevel@tonic-gate	INTR_POP
383*0Sstevel@tonic-gate	incq	(%rsp)
384*0Sstevel@tonic-gate	iretq
385*0Sstevel@tonic-gate
386*0Sstevel@tonic-gateud_ret:
387*0Sstevel@tonic-gate	INTR_POP
388*0Sstevel@tonic-gate	pushq	%rax			/* push temp */
389*0Sstevel@tonic-gate	movq	32(%rsp), %rax		/* load %rsp */
390*0Sstevel@tonic-gate	movq	(%rax), %rax		/* load calling RIP */
391*0Sstevel@tonic-gate	movq	%rax, 8(%rsp)		/* store calling RIP */
392*0Sstevel@tonic-gate	addq	$8, 32(%rsp)		/* adjust new %rsp */
393*0Sstevel@tonic-gate	popq	%rax			/* pop off temp */
394*0Sstevel@tonic-gate	iretq				/* return from interrupt */
395*0Sstevel@tonic-gate
396*0Sstevel@tonic-gateud_trap:
397*0Sstevel@tonic-gate	/*
398*0Sstevel@tonic-gate	 * We're going to let the kernel handle this as a normal #UD.  If,
399*0Sstevel@tonic-gate	 * however, we came through #BP and are spoofing #UD (in this case,
400*0Sstevel@tonic-gate	 * the stored error value will be non-zero), we need to de-spoof
401*0Sstevel@tonic-gate	 * the trap by incrementing %rip and pushing T_BPTFLT.
402*0Sstevel@tonic-gate	 */
403*0Sstevel@tonic-gate	cmpq	$0, REGOFF_ERR(%rsp)
404*0Sstevel@tonic-gate	je	ud_ud
405*0Sstevel@tonic-gate	incq	REGOFF_RIP(%rsp)
406*0Sstevel@tonic-gate	addq	$REGOFF_RIP, %rsp
407*0Sstevel@tonic-gate	TRAP_NOERR(T_BPTFLT)	/* $3 */
408*0Sstevel@tonic-gate	jmp	cmntrap
409*0Sstevel@tonic-gate
410*0Sstevel@tonic-gateud_ud:
411*0Sstevel@tonic-gate	addq	$REGOFF_RIP, %rsp
412*0Sstevel@tonic-gateud_user:
413*0Sstevel@tonic-gate	TRAP_NOERR(T_ILLINST)
414*0Sstevel@tonic-gate	jmp	cmntrap
415*0Sstevel@tonic-gate	SET_SIZE(invoptrap)
416*0Sstevel@tonic-gate
417*0Sstevel@tonic-gate#elif defined(__i386)
418*0Sstevel@tonic-gate
419*0Sstevel@tonic-gate	/*
420*0Sstevel@tonic-gate	 * #UD
421*0Sstevel@tonic-gate	 */
422*0Sstevel@tonic-gate	ENTRY_NP(invoptrap)
423*0Sstevel@tonic-gate	/*
424*0Sstevel@tonic-gate	 * If we are taking an invalid opcode trap while in the kernel, this
425*0Sstevel@tonic-gate	 * is likely an FBT probe point.
426*0Sstevel@tonic-gate	 */
427*0Sstevel@tonic-gate	pushl   %gs
428*0Sstevel@tonic-gate	cmpw	$KGS_SEL, (%esp)
429*0Sstevel@tonic-gate	jne	8f
430*0Sstevel@tonic-gate	addl	$4, %esp
431*0Sstevel@tonic-gate	pusha
432*0Sstevel@tonic-gate	pushl	%eax			/* push %eax -- may be return value */
433*0Sstevel@tonic-gate	pushl	%esp			/* push stack pointer */
434*0Sstevel@tonic-gate	addl	$48, (%esp)		/* adjust to incoming args */
435*0Sstevel@tonic-gate	pushl	40(%esp)		/* push calling EIP */
436*0Sstevel@tonic-gate	call	dtrace_invop
437*0Sstevel@tonic-gate	ALTENTRY(dtrace_invop_callsite)
438*0Sstevel@tonic-gate	addl	$12, %esp
439*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_PUSHL_EBP, %eax
440*0Sstevel@tonic-gate	je	1f
441*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_POPL_EBP, %eax
442*0Sstevel@tonic-gate	je	2f
443*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_LEAVE, %eax
444*0Sstevel@tonic-gate	je	3f
445*0Sstevel@tonic-gate	cmpl	$DTRACE_INVOP_NOP, %eax
446*0Sstevel@tonic-gate	je	4f
447*0Sstevel@tonic-gate	jmp	7f
448*0Sstevel@tonic-gate
449*0Sstevel@tonic-gate1:
450*0Sstevel@tonic-gate	/*
451*0Sstevel@tonic-gate	 * We must emulate a "pushl %ebp".  To do this, we pull the stack
452*0Sstevel@tonic-gate	 * down 4 bytes, and then store the base pointer.
453*0Sstevel@tonic-gate	 */
454*0Sstevel@tonic-gate	popa
455*0Sstevel@tonic-gate	subl	$4, %esp		/* make room for %ebp */
456*0Sstevel@tonic-gate	pushl	%eax			/* push temp */
457*0Sstevel@tonic-gate	movl	8(%esp), %eax		/* load calling EIP */
458*0Sstevel@tonic-gate	incl	%eax			/* increment over LOCK prefix */
459*0Sstevel@tonic-gate	movl	%eax, 4(%esp)		/* store calling EIP */
460*0Sstevel@tonic-gate	movl	12(%esp), %eax		/* load calling CS */
461*0Sstevel@tonic-gate	movl	%eax, 8(%esp)		/* store calling CS */
462*0Sstevel@tonic-gate	movl	16(%esp), %eax		/* load calling EFLAGS */
463*0Sstevel@tonic-gate	movl	%eax, 12(%esp)		/* store calling EFLAGS */
464*0Sstevel@tonic-gate	movl	%ebp, 16(%esp)		/* push %ebp */
465*0Sstevel@tonic-gate	popl	%eax			/* pop off temp */
466*0Sstevel@tonic-gate	iret				/* return from interrupt */
467*0Sstevel@tonic-gate
468*0Sstevel@tonic-gate2:
469*0Sstevel@tonic-gate	/*
470*0Sstevel@tonic-gate	 * We must emulate a "popl %ebp".  To do this, we do the opposite of
471*0Sstevel@tonic-gate	 * the above:  we remove the %ebp from the stack, and squeeze up the
472*0Sstevel@tonic-gate	 * saved state from the trap.
473*0Sstevel@tonic-gate	 */
474*0Sstevel@tonic-gate	popa
475*0Sstevel@tonic-gate	pushl	%eax			/* push temp */
476*0Sstevel@tonic-gate	movl	16(%esp), %ebp		/* pop %ebp */
477*0Sstevel@tonic-gate	movl	12(%esp), %eax		/* load calling EFLAGS */
478*0Sstevel@tonic-gate	movl	%eax, 16(%esp)		/* store calling EFLAGS */
479*0Sstevel@tonic-gate	movl	8(%esp), %eax		/* load calling CS */
480*0Sstevel@tonic-gate	movl	%eax, 12(%esp)		/* store calling CS */
481*0Sstevel@tonic-gate	movl	4(%esp), %eax		/* load calling EIP */
482*0Sstevel@tonic-gate	incl	%eax			/* increment over LOCK prefix */
483*0Sstevel@tonic-gate	movl	%eax, 8(%esp)		/* store calling EIP */
484*0Sstevel@tonic-gate	popl	%eax			/* pop off temp */
485*0Sstevel@tonic-gate	addl	$4, %esp		/* adjust stack pointer */
486*0Sstevel@tonic-gate	iret				/* return from interrupt */
487*0Sstevel@tonic-gate
488*0Sstevel@tonic-gate3:
489*0Sstevel@tonic-gate	/*
490*0Sstevel@tonic-gate	 * We must emulate a "leave", which is the same as a "movl %ebp, %esp"
491*0Sstevel@tonic-gate	 * followed by a "popl %ebp".  This looks similar to the above, but
492*0Sstevel@tonic-gate	 * requires two temporaries:  one for the new base pointer, and one
493*0Sstevel@tonic-gate	 * for the staging register.
494*0Sstevel@tonic-gate	 */
495*0Sstevel@tonic-gate	popa
496*0Sstevel@tonic-gate	pushl	%eax			/* push temp */
497*0Sstevel@tonic-gate	pushl	%ebx			/* push temp */
498*0Sstevel@tonic-gate	movl	%ebp, %ebx		/* set temp to old %ebp */
499*0Sstevel@tonic-gate	movl	(%ebx), %ebp		/* pop %ebp */
500*0Sstevel@tonic-gate	movl	16(%esp), %eax		/* load calling EFLAGS */
501*0Sstevel@tonic-gate	movl	%eax, (%ebx)		/* store calling EFLAGS */
502*0Sstevel@tonic-gate	movl	12(%esp), %eax		/* load calling CS */
503*0Sstevel@tonic-gate	movl	%eax, -4(%ebx)		/* store calling CS */
504*0Sstevel@tonic-gate	movl	8(%esp), %eax		/* load calling EIP */
505*0Sstevel@tonic-gate	incl	%eax			/* increment over LOCK prefix */
506*0Sstevel@tonic-gate	movl	%eax, -8(%ebx)		/* store calling EIP */
507*0Sstevel@tonic-gate	movl	%ebx, -4(%esp)		/* temporarily store new %esp */
508*0Sstevel@tonic-gate	popl	%ebx			/* pop off temp */
509*0Sstevel@tonic-gate	popl	%eax			/* pop off temp */
510*0Sstevel@tonic-gate	movl	-12(%esp), %esp		/* set stack pointer */
511*0Sstevel@tonic-gate	subl	$8, %esp		/* adjust for three pushes, one pop */
512*0Sstevel@tonic-gate	iret				/* return from interrupt */
513*0Sstevel@tonic-gate
514*0Sstevel@tonic-gate4:
515*0Sstevel@tonic-gate	/*
516*0Sstevel@tonic-gate	 * We must emulate a "nop".  This is obviously not hard:  we need only
517*0Sstevel@tonic-gate	 * advance the %eip by one.
518*0Sstevel@tonic-gate	 */
519*0Sstevel@tonic-gate	popa
520*0Sstevel@tonic-gate	incl	(%esp)
521*0Sstevel@tonic-gate	iret
522*0Sstevel@tonic-gate
523*0Sstevel@tonic-gate7:
524*0Sstevel@tonic-gate	popa
525*0Sstevel@tonic-gate	pushl	$0
526*0Sstevel@tonic-gate	pushl	$T_ILLINST	/* $6 */
527*0Sstevel@tonic-gate	jmp	cmntrap
528*0Sstevel@tonic-gate8:
529*0Sstevel@tonic-gate	addl	$4, %esp
530*0Sstevel@tonic-gate	pushl	$0
531*0Sstevel@tonic-gate	pushl	$T_ILLINST	/* $6 */
532*0Sstevel@tonic-gate	jmp	cmntrap
533*0Sstevel@tonic-gate	SET_SIZE(invoptrap)
534*0Sstevel@tonic-gate
535*0Sstevel@tonic-gate#endif	/* __i386 */
536*0Sstevel@tonic-gate
537*0Sstevel@tonic-gate#if defined(__amd64)
538*0Sstevel@tonic-gate
539*0Sstevel@tonic-gate	/*
540*0Sstevel@tonic-gate	 * #NM
541*0Sstevel@tonic-gate	 */
542*0Sstevel@tonic-gate	ENTRY_NP(ndptrap)
543*0Sstevel@tonic-gate	/*
544*0Sstevel@tonic-gate	 * We want to do this quickly as every lwp using fp will take this
545*0Sstevel@tonic-gate	 * after a context switch -- we do the frequent path in ndptrap_frstor
546*0Sstevel@tonic-gate	 * below; for all other cases, we let the trap code handle it
547*0Sstevel@tonic-gate	 */
548*0Sstevel@tonic-gate	pushq	%rax
549*0Sstevel@tonic-gate	pushq	%rbx
550*0Sstevel@tonic-gate	cmpw    $KCS_SEL, 24(%rsp)	/* did we come from kernel mode? */
551*0Sstevel@tonic-gate	jne     1f
552*0Sstevel@tonic-gate	LOADCPU(%rbx)			/* if yes, don't swapgs */
553*0Sstevel@tonic-gate	jmp	2f
554*0Sstevel@tonic-gate1:
555*0Sstevel@tonic-gate	swapgs				/* if from user, need swapgs */
556*0Sstevel@tonic-gate	LOADCPU(%rbx)
557*0Sstevel@tonic-gate	swapgs
558*0Sstevel@tonic-gate2:
559*0Sstevel@tonic-gate	cmpl	$0, fpu_exists(%rip)
560*0Sstevel@tonic-gate	je	.handle_in_trap		/* let trap handle no fp case */
561*0Sstevel@tonic-gate	movq	CPU_THREAD(%rbx), %rax	/* %rax = curthread */
562*0Sstevel@tonic-gate	movl	$FPU_EN, %ebx
563*0Sstevel@tonic-gate	movq	T_LWP(%rax), %rax	/* %rax = lwp */
564*0Sstevel@tonic-gate	testq	%rax, %rax
565*0Sstevel@tonic-gate	jz	.handle_in_trap		/* should not happen? */
566*0Sstevel@tonic-gate#if LWP_PCB_FPU	!= 0
567*0Sstevel@tonic-gate	addq	$LWP_PCB_FPU, %rax	/* &lwp->lwp_pcb.pcb_fpu */
568*0Sstevel@tonic-gate#endif
569*0Sstevel@tonic-gate	testl	%ebx, PCB_FPU_FLAGS(%rax)
570*0Sstevel@tonic-gate	jz	.handle_in_trap		/* must be the first fault */
571*0Sstevel@tonic-gate	clts
572*0Sstevel@tonic-gate	andl	$_BITNOT(FPU_VALID), PCB_FPU_FLAGS(%rax)
573*0Sstevel@tonic-gate#if FPU_CTX_FPU_REGS != 0
574*0Sstevel@tonic-gate	addq	$FPU_CTX_FPU_REGS, %rax
575*0Sstevel@tonic-gate#endif
576*0Sstevel@tonic-gate	/*
577*0Sstevel@tonic-gate	 * the label below is used in trap.c to detect FP faults in
578*0Sstevel@tonic-gate	 * kernel due to user fault.
579*0Sstevel@tonic-gate	 */
580*0Sstevel@tonic-gate	ALTENTRY(ndptrap_frstor)
581*0Sstevel@tonic-gate	fxrstor	(%rax)
582*0Sstevel@tonic-gate	popq	%rbx
583*0Sstevel@tonic-gate	popq	%rax
584*0Sstevel@tonic-gate	iretq
585*0Sstevel@tonic-gate
586*0Sstevel@tonic-gate.handle_in_trap:
587*0Sstevel@tonic-gate	popq	%rbx
588*0Sstevel@tonic-gate	popq	%rax
589*0Sstevel@tonic-gate	TRAP_NOERR(T_NOEXTFLT)	/* $7 */
590*0Sstevel@tonic-gate	jmp	cmninttrap
591*0Sstevel@tonic-gate	SET_SIZE(ndptrap_frstor)
592*0Sstevel@tonic-gate	SET_SIZE(ndptrap)
593*0Sstevel@tonic-gate
594*0Sstevel@tonic-gate#elif defined(__i386)
595*0Sstevel@tonic-gate
596*0Sstevel@tonic-gate	ENTRY_NP(ndptrap)
597*0Sstevel@tonic-gate	/*
598*0Sstevel@tonic-gate	 * We want to do this quickly as every lwp using fp will take this
599*0Sstevel@tonic-gate	 * after a context switch -- we do the frequent path in fpnoextflt
600*0Sstevel@tonic-gate	 * below; for all other cases, we let the trap code handle it
601*0Sstevel@tonic-gate	 */
602*0Sstevel@tonic-gate	pushl	%eax
603*0Sstevel@tonic-gate	pushl	%ebx
604*0Sstevel@tonic-gate	pushl	%ds
605*0Sstevel@tonic-gate	pushl	%gs
606*0Sstevel@tonic-gate	movl	$KDS_SEL, %ebx
607*0Sstevel@tonic-gate	movw	%bx, %ds
608*0Sstevel@tonic-gate	movl	$KGS_SEL, %eax
609*0Sstevel@tonic-gate	movw	%ax, %gs
610*0Sstevel@tonic-gate	LOADCPU(%ebx)
611*0Sstevel@tonic-gate	cmpl	$0, fpu_exists
612*0Sstevel@tonic-gate	je	.handle_in_trap		/* let trap handle no fp case */
613*0Sstevel@tonic-gate	movl	CPU_THREAD(%ebx), %eax	/* %eax = curthread */
614*0Sstevel@tonic-gate	movl	$FPU_EN, %ebx
615*0Sstevel@tonic-gate	movl	T_LWP(%eax), %eax	/* %eax = lwp */
616*0Sstevel@tonic-gate	testl	%eax, %eax
617*0Sstevel@tonic-gate	jz	.handle_in_trap		/* should not happen? */
618*0Sstevel@tonic-gate#if LWP_PCB_FPU != 0
619*0Sstevel@tonic-gate	addl	$LWP_PCB_FPU, %eax 	/* &lwp->lwp_pcb.pcb_fpu */
620*0Sstevel@tonic-gate#endif
621*0Sstevel@tonic-gate	testl	%ebx, PCB_FPU_FLAGS(%eax)
622*0Sstevel@tonic-gate	jz	.handle_in_trap		/* must be the first fault */
623*0Sstevel@tonic-gate	clts
624*0Sstevel@tonic-gate	andl	$_BITNOT(FPU_VALID), PCB_FPU_FLAGS(%eax)
625*0Sstevel@tonic-gate#if FPU_CTX_FPU_REGS != 0
626*0Sstevel@tonic-gate	addl	$FPU_CTX_FPU_REGS, %eax
627*0Sstevel@tonic-gate#endif
628*0Sstevel@tonic-gate	/*
629*0Sstevel@tonic-gate	 * the label below is used in trap.c to detect FP faults in kernel
630*0Sstevel@tonic-gate	 * due to user fault.
631*0Sstevel@tonic-gate	 */
632*0Sstevel@tonic-gate	ALTENTRY(ndptrap_frstor)
633*0Sstevel@tonic-gate	.globl	_patch_fxrstor_eax
634*0Sstevel@tonic-gate_patch_fxrstor_eax:
635*0Sstevel@tonic-gate	frstor	(%eax)		/* may be patched to fxrstor */
636*0Sstevel@tonic-gate	nop			/* (including this byte) */
637*0Sstevel@tonic-gate	popl	%gs
638*0Sstevel@tonic-gate	popl	%ds
639*0Sstevel@tonic-gate	popl	%ebx
640*0Sstevel@tonic-gate	popl	%eax
641*0Sstevel@tonic-gate	iret
642*0Sstevel@tonic-gate
643*0Sstevel@tonic-gate.handle_in_trap:
644*0Sstevel@tonic-gate	popl	%gs
645*0Sstevel@tonic-gate	popl	%ds
646*0Sstevel@tonic-gate	popl	%ebx
647*0Sstevel@tonic-gate	popl	%eax
648*0Sstevel@tonic-gate	pushl	$0
649*0Sstevel@tonic-gate	pushl	$T_NOEXTFLT	/* $7 */
650*0Sstevel@tonic-gate	jmp	cmninttrap
651*0Sstevel@tonic-gate	SET_SIZE(ndptrap_frstor)
652*0Sstevel@tonic-gate	SET_SIZE(ndptrap)
653*0Sstevel@tonic-gate
654*0Sstevel@tonic-gate#endif	/* __i386 */
655*0Sstevel@tonic-gate
656*0Sstevel@tonic-gate#if defined(__amd64)
657*0Sstevel@tonic-gate
658*0Sstevel@tonic-gate	/*
659*0Sstevel@tonic-gate	 * #DF
660*0Sstevel@tonic-gate	 */
661*0Sstevel@tonic-gate	ENTRY_NP(syserrtrap)
662*0Sstevel@tonic-gate	pushq	$T_DBLFLT
663*0Sstevel@tonic-gate
664*0Sstevel@tonic-gate	SET_CPU_GSBASE
665*0Sstevel@tonic-gate
666*0Sstevel@tonic-gate	/*
667*0Sstevel@tonic-gate	 * We share this handler with kmdb (if kmdb is loaded).  As such, we may
668*0Sstevel@tonic-gate	 * have reached this point after encountering a #df in kmdb.  If that
669*0Sstevel@tonic-gate	 * happens, we'll still be on kmdb's IDT.  We need to switch back to this
670*0Sstevel@tonic-gate	 * CPU's IDT before proceeding.  Furthermore, if we did arrive here from
671*0Sstevel@tonic-gate	 * kmdb, kmdb is probably in a very sickly state, and shouldn't be
672*0Sstevel@tonic-gate	 * entered from the panic flow.  We'll suppress that entry by setting
673*0Sstevel@tonic-gate	 * nopanicdebug.
674*0Sstevel@tonic-gate	 */
675*0Sstevel@tonic-gate	pushq	%rax
676*0Sstevel@tonic-gate	subq	$DESCTBR_SIZE, %rsp
677*0Sstevel@tonic-gate	sidt	(%rsp)
678*0Sstevel@tonic-gate	movq	%gs:CPU_IDT, %rax
679*0Sstevel@tonic-gate	cmpq	%rax, DTR_BASE(%rsp)
680*0Sstevel@tonic-gate	je	1f
681*0Sstevel@tonic-gate
682*0Sstevel@tonic-gate	movq	%rax, DTR_BASE(%rsp)
683*0Sstevel@tonic-gate	movw	$_MUL(NIDT, GATE_DESC_SIZE), DTR_LIMIT(%rsp)
684*0Sstevel@tonic-gate	lidt	(%rsp)
685*0Sstevel@tonic-gate
686*0Sstevel@tonic-gate	movl	$1, nopanicdebug
687*0Sstevel@tonic-gate
688*0Sstevel@tonic-gate1:	addq	$DESCTBR_SIZE, %rsp
689*0Sstevel@tonic-gate	popq	%rax
690*0Sstevel@tonic-gate
691*0Sstevel@tonic-gate	DFTRAP_PUSH
692*0Sstevel@tonic-gate
693*0Sstevel@tonic-gate	/*
694*0Sstevel@tonic-gate	 * freeze trap trace.
695*0Sstevel@tonic-gate	 */
696*0Sstevel@tonic-gate#ifdef TRAPTRACE
697*0Sstevel@tonic-gate	leaq	trap_trace_freeze(%rip), %r11
698*0Sstevel@tonic-gate	incl	(%r11)
699*0Sstevel@tonic-gate#endif
700*0Sstevel@tonic-gate
701*0Sstevel@tonic-gate	ENABLE_INTR_FLAGS
702*0Sstevel@tonic-gate
703*0Sstevel@tonic-gate	movq	%rsp, %rdi	/* &regs */
704*0Sstevel@tonic-gate	xorl	%esi, %esi	/* clear address */
705*0Sstevel@tonic-gate	xorl	%edx, %edx	/* cpuid = 0 */
706*0Sstevel@tonic-gate	call	trap
707*0Sstevel@tonic-gate
708*0Sstevel@tonic-gate	SET_SIZE(syserrtrap)
709*0Sstevel@tonic-gate
710*0Sstevel@tonic-gate#elif defined(__i386)
711*0Sstevel@tonic-gate
712*0Sstevel@tonic-gate	/*
713*0Sstevel@tonic-gate	 * #DF
714*0Sstevel@tonic-gate	 */
715*0Sstevel@tonic-gate	ENTRY_NP(syserrtrap)
716*0Sstevel@tonic-gate	cli				/* disable interrupts */
717*0Sstevel@tonic-gate
718*0Sstevel@tonic-gate	/*
719*0Sstevel@tonic-gate	 * We share this handler with kmdb (if kmdb is loaded).  As such, we may
720*0Sstevel@tonic-gate	 * have reached this point after encountering a #df in kmdb.  If that
721*0Sstevel@tonic-gate	 * happens, we'll still be on kmdb's IDT.  We need to switch back to this
722*0Sstevel@tonic-gate	 * CPU's IDT before proceeding.  Furthermore, if we did arrive here from
723*0Sstevel@tonic-gate	 * kmdb, kmdb is probably in a very sickly state, and shouldn't be
724*0Sstevel@tonic-gate	 * entered from the panic flow.  We'll suppress that entry by setting
725*0Sstevel@tonic-gate	 * nopanicdebug.
726*0Sstevel@tonic-gate	 */
727*0Sstevel@tonic-gate	subl	$DESCTBR_SIZE, %esp
728*0Sstevel@tonic-gate	movl	%gs:CPU_IDT, %eax
729*0Sstevel@tonic-gate	sidt	(%esp)
730*0Sstevel@tonic-gate	cmpl	DTR_BASE(%esp), %eax
731*0Sstevel@tonic-gate	je	1f
732*0Sstevel@tonic-gate
733*0Sstevel@tonic-gate	movl	%eax, DTR_BASE(%esp)
734*0Sstevel@tonic-gate	movw	$_MUL(NIDT, GATE_DESC_SIZE), DTR_LIMIT(%esp)
735*0Sstevel@tonic-gate	lidt	(%esp)
736*0Sstevel@tonic-gate
737*0Sstevel@tonic-gate	movl	$1, nopanicdebug
738*0Sstevel@tonic-gate
739*0Sstevel@tonic-gate1:	addl	$DESCTBR_SIZE, %esp
740*0Sstevel@tonic-gate
741*0Sstevel@tonic-gate	/*
742*0Sstevel@tonic-gate	 * Check the CPL in the TSS to see what mode
743*0Sstevel@tonic-gate	 * (user or kernel) we took the fault in.  At this
744*0Sstevel@tonic-gate	 * point we are running in the context of the double
745*0Sstevel@tonic-gate	 * fault task (dftss) but the CPU's task points to
746*0Sstevel@tonic-gate	 * the previous task (ktss) where the process context
747*0Sstevel@tonic-gate	 * has been saved as the result of the task switch.
748*0Sstevel@tonic-gate	 */
749*0Sstevel@tonic-gate	movl	%gs:CPU_TSS, %eax	/* get the TSS */
750*0Sstevel@tonic-gate	movl	TSS_SS(%eax), %ebx	/* save the fault SS */
751*0Sstevel@tonic-gate	movl	TSS_ESP(%eax), %edx	/* save the fault ESP */
752*0Sstevel@tonic-gate	testw	$CPL_MASK, TSS_CS(%eax)	/* user mode ? */
753*0Sstevel@tonic-gate	jz	make_frame
754*0Sstevel@tonic-gate	movw	TSS_SS0(%eax), %ss	/* get on the kernel stack */
755*0Sstevel@tonic-gate	movl	TSS_ESP0(%eax), %esp
756*0Sstevel@tonic-gate
757*0Sstevel@tonic-gate	/*
758*0Sstevel@tonic-gate	 * Clear the NT flag to avoid a task switch when the process
759*0Sstevel@tonic-gate	 * finally pops the EFL off the stack via an iret.  Clear
760*0Sstevel@tonic-gate	 * the TF flag since that is what the processor does for
761*0Sstevel@tonic-gate	 * a normal exception. Clear the IE flag so that interrupts
762*0Sstevel@tonic-gate	 * remain disabled.
763*0Sstevel@tonic-gate	 */
764*0Sstevel@tonic-gate	movl	TSS_EFL(%eax), %ecx
765*0Sstevel@tonic-gate	andl	$_BITNOT(PS_NT|PS_T|PS_IE), %ecx
766*0Sstevel@tonic-gate	pushl	%ecx
767*0Sstevel@tonic-gate	popfl				/* restore the EFL */
768*0Sstevel@tonic-gate	movw	TSS_LDT(%eax), %cx	/* restore the LDT */
769*0Sstevel@tonic-gate	lldt	%cx
770*0Sstevel@tonic-gate
771*0Sstevel@tonic-gate	/*
772*0Sstevel@tonic-gate	 * Restore process segment selectors.
773*0Sstevel@tonic-gate	 */
774*0Sstevel@tonic-gate	movw	TSS_DS(%eax), %ds
775*0Sstevel@tonic-gate	movw	TSS_ES(%eax), %es
776*0Sstevel@tonic-gate	movw	TSS_FS(%eax), %fs
777*0Sstevel@tonic-gate	movw	TSS_GS(%eax), %gs
778*0Sstevel@tonic-gate
779*0Sstevel@tonic-gate	/*
780*0Sstevel@tonic-gate	 * Restore task segment selectors.
781*0Sstevel@tonic-gate	 */
782*0Sstevel@tonic-gate	movl	$KDS_SEL, TSS_DS(%eax)
783*0Sstevel@tonic-gate	movl	$KDS_SEL, TSS_ES(%eax)
784*0Sstevel@tonic-gate	movl	$KDS_SEL, TSS_SS(%eax)
785*0Sstevel@tonic-gate	movl	$KFS_SEL, TSS_FS(%eax)
786*0Sstevel@tonic-gate	movl	$KGS_SEL, TSS_GS(%eax)
787*0Sstevel@tonic-gate
788*0Sstevel@tonic-gate	/*
789*0Sstevel@tonic-gate	 * Clear the TS bit, the busy bits in both task
790*0Sstevel@tonic-gate	 * descriptors, and switch tasks.
791*0Sstevel@tonic-gate	 */
792*0Sstevel@tonic-gate	clts
793*0Sstevel@tonic-gate	leal	gdt0, %ecx
794*0Sstevel@tonic-gate	movl	DFTSS_SEL+4(%ecx), %esi
795*0Sstevel@tonic-gate	andl	$_BITNOT(0x200), %esi
796*0Sstevel@tonic-gate	movl	%esi, DFTSS_SEL+4(%ecx)
797*0Sstevel@tonic-gate	movl	KTSS_SEL+4(%ecx), %esi
798*0Sstevel@tonic-gate	andl	$_BITNOT(0x200), %esi
799*0Sstevel@tonic-gate	movl	%esi, KTSS_SEL+4(%ecx)
800*0Sstevel@tonic-gate	movw	$KTSS_SEL, %cx
801*0Sstevel@tonic-gate	ltr	%cx
802*0Sstevel@tonic-gate
803*0Sstevel@tonic-gate	/*
804*0Sstevel@tonic-gate	 * Restore part of the process registers.
805*0Sstevel@tonic-gate	 */
806*0Sstevel@tonic-gate	movl	TSS_EBP(%eax), %ebp
807*0Sstevel@tonic-gate	movl	TSS_ECX(%eax), %ecx
808*0Sstevel@tonic-gate	movl	TSS_ESI(%eax), %esi
809*0Sstevel@tonic-gate	movl	TSS_EDI(%eax), %edi
810*0Sstevel@tonic-gate
811*0Sstevel@tonic-gatemake_frame:
812*0Sstevel@tonic-gate	/*
813*0Sstevel@tonic-gate	 * Make a trap frame.  Leave the error code (0) on
814*0Sstevel@tonic-gate	 * the stack since the first word on a trap stack is
815*0Sstevel@tonic-gate	 * unused anyway.
816*0Sstevel@tonic-gate	 */
817*0Sstevel@tonic-gate	pushl	%ebx			/ fault SS
818*0Sstevel@tonic-gate	pushl	%edx			/ fault ESP
819*0Sstevel@tonic-gate	pushl	TSS_EFL(%eax)		/ fault EFL
820*0Sstevel@tonic-gate	pushl	TSS_CS(%eax)		/ fault CS
821*0Sstevel@tonic-gate	pushl	TSS_EIP(%eax)		/ fault EIP
822*0Sstevel@tonic-gate	pushl	$0			/ error code
823*0Sstevel@tonic-gate	pushl	$T_DBLFLT		/ trap number 8
824*0Sstevel@tonic-gate	movl	TSS_EBX(%eax), %ebx	/ restore EBX
825*0Sstevel@tonic-gate	movl	TSS_EDX(%eax), %edx	/ restore EDX
826*0Sstevel@tonic-gate	movl	TSS_EAX(%eax), %eax	/ restore EAX
827*0Sstevel@tonic-gate	sti				/ enable interrupts
828*0Sstevel@tonic-gate	jmp	cmntrap
829*0Sstevel@tonic-gate	SET_SIZE(syserrtrap)
830*0Sstevel@tonic-gate
831*0Sstevel@tonic-gate#endif	/* __i386 */
832*0Sstevel@tonic-gate
833*0Sstevel@tonic-gate	ENTRY_NP(overrun)
834*0Sstevel@tonic-gate	push	$0
835*0Sstevel@tonic-gate	TRAP_NOERR(T_EXTOVRFLT)	/* $9 i386 only - not generated */
836*0Sstevel@tonic-gate	jmp	cmninttrap
837*0Sstevel@tonic-gate	SET_SIZE(overrun)
838*0Sstevel@tonic-gate
839*0Sstevel@tonic-gate	/*
840*0Sstevel@tonic-gate	 * #TS
841*0Sstevel@tonic-gate	 */
842*0Sstevel@tonic-gate	ENTRY_NP(invtsstrap)
843*0Sstevel@tonic-gate	TRAP_ERR(T_TSSFLT)	/* $10 already have error code on stack */
844*0Sstevel@tonic-gate	jmp	cmntrap
845*0Sstevel@tonic-gate	SET_SIZE(invtsstrap)
846*0Sstevel@tonic-gate
847*0Sstevel@tonic-gate	/*
848*0Sstevel@tonic-gate	 * #NP
849*0Sstevel@tonic-gate	 */
850*0Sstevel@tonic-gate	ENTRY_NP(segnptrap)
851*0Sstevel@tonic-gate	TRAP_ERR(T_SEGFLT)	/* $11 already have error code on stack */
852*0Sstevel@tonic-gate#if defined(__amd64)
853*0Sstevel@tonic-gate	SET_CPU_GSBASE
854*0Sstevel@tonic-gate#endif
855*0Sstevel@tonic-gate	jmp	cmntrap
856*0Sstevel@tonic-gate	SET_SIZE(segnptrap)
857*0Sstevel@tonic-gate
858*0Sstevel@tonic-gate	/*
859*0Sstevel@tonic-gate	 * #SS
860*0Sstevel@tonic-gate	 */
861*0Sstevel@tonic-gate	ENTRY_NP(stktrap)
862*0Sstevel@tonic-gate	TRAP_ERR(T_STKFLT)	/* $12 already have error code on stack */
863*0Sstevel@tonic-gate	jmp	cmntrap
864*0Sstevel@tonic-gate	SET_SIZE(stktrap)
865*0Sstevel@tonic-gate
866*0Sstevel@tonic-gate	/*
867*0Sstevel@tonic-gate	 * #GP
868*0Sstevel@tonic-gate	 */
869*0Sstevel@tonic-gate	ENTRY_NP(gptrap)
870*0Sstevel@tonic-gate	TRAP_ERR(T_GPFLT)	/* $13 already have error code on stack */
871*0Sstevel@tonic-gate#if defined(__amd64)
872*0Sstevel@tonic-gate	SET_CPU_GSBASE
873*0Sstevel@tonic-gate#endif
874*0Sstevel@tonic-gate	jmp	cmntrap
875*0Sstevel@tonic-gate	SET_SIZE(gptrap)
876*0Sstevel@tonic-gate
877*0Sstevel@tonic-gate	/*
878*0Sstevel@tonic-gate	 * #PF
879*0Sstevel@tonic-gate	 */
880*0Sstevel@tonic-gate	ENTRY_NP(pftrap)
881*0Sstevel@tonic-gate	TRAP_ERR(T_PGFLT)	/* $14 already have error code on stack */
882*0Sstevel@tonic-gate	jmp	cmntrap
883*0Sstevel@tonic-gate	SET_SIZE(pftrap)
884*0Sstevel@tonic-gate
885*0Sstevel@tonic-gate#if !defined(__amd64)
886*0Sstevel@tonic-gate
887*0Sstevel@tonic-gate	/*
888*0Sstevel@tonic-gate	 * #PF pentium bug workaround
889*0Sstevel@tonic-gate	 */
890*0Sstevel@tonic-gate	ENTRY_NP(pentium_pftrap)
891*0Sstevel@tonic-gate	pushl	%eax
892*0Sstevel@tonic-gate	movl	%cr2, %eax
893*0Sstevel@tonic-gate	andl	$MMU_STD_PAGEMASK, %eax
894*0Sstevel@tonic-gate
895*0Sstevel@tonic-gate	cmpl	%eax, %cs:idt0_default_r+2	/* fixme */
896*0Sstevel@tonic-gate
897*0Sstevel@tonic-gate	je	check_for_user_address
898*0Sstevel@tonic-gateuser_mode:
899*0Sstevel@tonic-gate	popl	%eax
900*0Sstevel@tonic-gate	pushl	$T_PGFLT	/* $14 */
901*0Sstevel@tonic-gate	jmp	cmntrap
902*0Sstevel@tonic-gatecheck_for_user_address:
903*0Sstevel@tonic-gate	/*
904*0Sstevel@tonic-gate	 * Before we assume that we have an unmapped trap on our hands,
905*0Sstevel@tonic-gate	 * check to see if this is a fault from user mode.  If it is,
906*0Sstevel@tonic-gate	 * we'll kick back into the page fault handler.
907*0Sstevel@tonic-gate	 */
908*0Sstevel@tonic-gate	movl	4(%esp), %eax	/* error code */
909*0Sstevel@tonic-gate	andl	$PF_ERR_USER, %eax
910*0Sstevel@tonic-gate	jnz	user_mode
911*0Sstevel@tonic-gate
912*0Sstevel@tonic-gate	/*
913*0Sstevel@tonic-gate	 * We now know that this is the invalid opcode trap.
914*0Sstevel@tonic-gate	 */
915*0Sstevel@tonic-gate	popl	%eax
916*0Sstevel@tonic-gate	addl	$4, %esp	/* pop error code */
917*0Sstevel@tonic-gate	jmp	invoptrap
918*0Sstevel@tonic-gate	SET_SIZE(pentium_pftrap)
919*0Sstevel@tonic-gate
920*0Sstevel@tonic-gate#endif	/* !__amd64 */
921*0Sstevel@tonic-gate
922*0Sstevel@tonic-gate	ENTRY_NP(resvtrap)
923*0Sstevel@tonic-gate	TRAP_NOERR(15)		/* (reserved)  */
924*0Sstevel@tonic-gate	jmp	cmntrap
925*0Sstevel@tonic-gate	SET_SIZE(resvtrap)
926*0Sstevel@tonic-gate
927*0Sstevel@tonic-gate	/*
928*0Sstevel@tonic-gate	 * #MF
929*0Sstevel@tonic-gate	 */
930*0Sstevel@tonic-gate	ENTRY_NP(ndperr)
931*0Sstevel@tonic-gate	TRAP_NOERR(T_EXTERRFLT)	/* $16 */
932*0Sstevel@tonic-gate	jmp	cmninttrap
933*0Sstevel@tonic-gate	SET_SIZE(ndperr)
934*0Sstevel@tonic-gate
935*0Sstevel@tonic-gate	/*
936*0Sstevel@tonic-gate	 * #AC
937*0Sstevel@tonic-gate	 */
938*0Sstevel@tonic-gate	ENTRY_NP(achktrap)
939*0Sstevel@tonic-gate	TRAP_ERR(T_ALIGNMENT)	/* $17 */
940*0Sstevel@tonic-gate	jmp	cmntrap
941*0Sstevel@tonic-gate	SET_SIZE(achktrap)
942*0Sstevel@tonic-gate
943*0Sstevel@tonic-gate	/*
944*0Sstevel@tonic-gate	 * #MC
945*0Sstevel@tonic-gate	 */
946*0Sstevel@tonic-gate	ENTRY_NP(mcetrap)
947*0Sstevel@tonic-gate	TRAP_NOERR(T_MCE)	/* $18 */
948*0Sstevel@tonic-gate	jmp	cmninttrap
949*0Sstevel@tonic-gate	SET_SIZE(mcetrap)
950*0Sstevel@tonic-gate
951*0Sstevel@tonic-gate	/*
952*0Sstevel@tonic-gate	 * #XF
953*0Sstevel@tonic-gate	 */
954*0Sstevel@tonic-gate	ENTRY_NP(xmtrap)
955*0Sstevel@tonic-gate	TRAP_NOERR(T_SIMDFPE)	/* $19 */
956*0Sstevel@tonic-gate	jmp	cmntrap
957*0Sstevel@tonic-gate	SET_SIZE(xmtrap)
958*0Sstevel@tonic-gate
959*0Sstevel@tonic-gate	ENTRY_NP(invaltrap)
960*0Sstevel@tonic-gate	TRAP_NOERR(30)		/* very invalid */
961*0Sstevel@tonic-gate	jmp	cmntrap
962*0Sstevel@tonic-gate	SET_SIZE(invaltrap)
963*0Sstevel@tonic-gate
964*0Sstevel@tonic-gate	ENTRY_NP(invalint)
965*0Sstevel@tonic-gate	TRAP_NOERR(31)		/* even more so */
966*0Sstevel@tonic-gate	jmp	cmnint
967*0Sstevel@tonic-gate	SET_SIZE(invalint)
968*0Sstevel@tonic-gate
969*0Sstevel@tonic-gate	.globl	fasttable
970*0Sstevel@tonic-gate
971*0Sstevel@tonic-gate#if defined(__amd64)
972*0Sstevel@tonic-gate
973*0Sstevel@tonic-gate	ENTRY_NP(fasttrap)
974*0Sstevel@tonic-gate	cmpl	$T_LASTFAST, %eax
975*0Sstevel@tonic-gate	ja	1f
976*0Sstevel@tonic-gate	orl	%eax, %eax	/* (zero extend top 32-bits) */
977*0Sstevel@tonic-gate	leaq	fasttable(%rip), %r11
978*0Sstevel@tonic-gate	leaq	(%r11, %rax, CLONGSIZE), %r11
979*0Sstevel@tonic-gate	jmp	*(%r11)
980*0Sstevel@tonic-gate1:
981*0Sstevel@tonic-gate	/*
982*0Sstevel@tonic-gate	 * Fast syscall number was illegal.  Make it look
983*0Sstevel@tonic-gate	 * as if the INT failed.  Modify %rip to point before the
984*0Sstevel@tonic-gate	 * INT, push the expected error code and fake a GP fault.
985*0Sstevel@tonic-gate	 *
986*0Sstevel@tonic-gate	 * XXX Why make the error code be offset into idt + 1?
987*0Sstevel@tonic-gate	 * Instead we should push a real (soft?) error code
988*0Sstevel@tonic-gate	 * on the stack and #gp handler could know about fasttraps?
989*0Sstevel@tonic-gate	 */
990*0Sstevel@tonic-gate	subq	$2, (%rsp)	/* XXX int insn 2-bytes */
991*0Sstevel@tonic-gate	pushq	$_CONST(_MUL(T_FASTTRAP, GATE_DESC_SIZE) + 2)
992*0Sstevel@tonic-gate	jmp	gptrap
993*0Sstevel@tonic-gate	SET_SIZE(fasttrap)
994*0Sstevel@tonic-gate
995*0Sstevel@tonic-gate#elif defined(__i386)
996*0Sstevel@tonic-gate
997*0Sstevel@tonic-gate	ENTRY_NP(fasttrap)
998*0Sstevel@tonic-gate	cmpl	$T_LASTFAST, %eax
999*0Sstevel@tonic-gate	ja	1f
1000*0Sstevel@tonic-gate	jmp	*%cs:fasttable(, %eax, CLONGSIZE)
1001*0Sstevel@tonic-gate1:
1002*0Sstevel@tonic-gate	/*
1003*0Sstevel@tonic-gate	 * Fast syscall number was illegal.  Make it look
1004*0Sstevel@tonic-gate	 * as if the INT failed.  Modify %eip to point before the
1005*0Sstevel@tonic-gate	 * INT, push the expected error code and fake a GP fault.
1006*0Sstevel@tonic-gate	 *
1007*0Sstevel@tonic-gate	 * XXX Why make the error code be offset into idt + 1?
1008*0Sstevel@tonic-gate	 * Instead we should push a real (soft?) error code
1009*0Sstevel@tonic-gate	 * on the stack and #gp handler could know about fasttraps?
1010*0Sstevel@tonic-gate	 */
1011*0Sstevel@tonic-gate	subl	$2, (%esp)	/* XXX int insn 2-bytes */
1012*0Sstevel@tonic-gate	pushl	$_CONST(_MUL(T_FASTTRAP, GATE_DESC_SIZE) + 2)
1013*0Sstevel@tonic-gate	jmp	gptrap
1014*0Sstevel@tonic-gate	SET_SIZE(fasttrap)
1015*0Sstevel@tonic-gate
1016*0Sstevel@tonic-gate#endif	/* __i386 */
1017*0Sstevel@tonic-gate
1018*0Sstevel@tonic-gate	ENTRY_NP(dtrace_fasttrap)
1019*0Sstevel@tonic-gate	TRAP_NOERR(T_DTRACE_PROBE)
1020*0Sstevel@tonic-gate	jmp	dtrace_trap
1021*0Sstevel@tonic-gate	SET_SIZE(dtrace_fasttrap)
1022*0Sstevel@tonic-gate
1023*0Sstevel@tonic-gate	ENTRY_NP(dtrace_ret)
1024*0Sstevel@tonic-gate	TRAP_NOERR(T_DTRACE_RET)
1025*0Sstevel@tonic-gate	jmp	dtrace_trap
1026*0Sstevel@tonic-gate	SET_SIZE(dtrace_ret)
1027*0Sstevel@tonic-gate
1028*0Sstevel@tonic-gate#if defined(__amd64)
1029*0Sstevel@tonic-gate
1030*0Sstevel@tonic-gate	/*
1031*0Sstevel@tonic-gate	 * RFLAGS 24 bytes up the stack from %rsp.
1032*0Sstevel@tonic-gate	 * XXX a constant would be nicer.
1033*0Sstevel@tonic-gate	 */
1034*0Sstevel@tonic-gate	ENTRY_NP(fast_null)
1035*0Sstevel@tonic-gate	orq	$PS_C, 24(%rsp)	/* set carry bit in user flags */
1036*0Sstevel@tonic-gate	iretq
1037*0Sstevel@tonic-gate	SET_SIZE(fast_null)
1038*0Sstevel@tonic-gate
1039*0Sstevel@tonic-gate#elif defined(__i386)
1040*0Sstevel@tonic-gate
1041*0Sstevel@tonic-gate	ENTRY_NP(fast_null)
1042*0Sstevel@tonic-gate	orw	$PS_C, 8(%esp)	/* set carry bit in user flags */
1043*0Sstevel@tonic-gate	iret
1044*0Sstevel@tonic-gate	SET_SIZE(fast_null)
1045*0Sstevel@tonic-gate
1046*0Sstevel@tonic-gate#endif	/* __i386 */
1047*0Sstevel@tonic-gate
1048*0Sstevel@tonic-gate	/*
1049*0Sstevel@tonic-gate	 * Interrupts start at 32
1050*0Sstevel@tonic-gate	 */
1051*0Sstevel@tonic-gate#define MKIVCT(n)			\
1052*0Sstevel@tonic-gate	ENTRY_NP(ivct/**/n)		\
1053*0Sstevel@tonic-gate	push	$0;			\
1054*0Sstevel@tonic-gate	push	$n - 0x20;		\
1055*0Sstevel@tonic-gate	jmp	cmnint;			\
1056*0Sstevel@tonic-gate	SET_SIZE(ivct/**/n)
1057*0Sstevel@tonic-gate
1058*0Sstevel@tonic-gate	MKIVCT(32)
1059*0Sstevel@tonic-gate	MKIVCT(33)
1060*0Sstevel@tonic-gate	MKIVCT(34)
1061*0Sstevel@tonic-gate	MKIVCT(35)
1062*0Sstevel@tonic-gate	MKIVCT(36)
1063*0Sstevel@tonic-gate	MKIVCT(37)
1064*0Sstevel@tonic-gate	MKIVCT(38)
1065*0Sstevel@tonic-gate	MKIVCT(39)
1066*0Sstevel@tonic-gate	MKIVCT(40)
1067*0Sstevel@tonic-gate	MKIVCT(41)
1068*0Sstevel@tonic-gate	MKIVCT(42)
1069*0Sstevel@tonic-gate	MKIVCT(43)
1070*0Sstevel@tonic-gate	MKIVCT(44)
1071*0Sstevel@tonic-gate	MKIVCT(45)
1072*0Sstevel@tonic-gate	MKIVCT(46)
1073*0Sstevel@tonic-gate	MKIVCT(47)
1074*0Sstevel@tonic-gate	MKIVCT(48)
1075*0Sstevel@tonic-gate	MKIVCT(49)
1076*0Sstevel@tonic-gate	MKIVCT(50)
1077*0Sstevel@tonic-gate	MKIVCT(51)
1078*0Sstevel@tonic-gate	MKIVCT(52)
1079*0Sstevel@tonic-gate	MKIVCT(53)
1080*0Sstevel@tonic-gate	MKIVCT(54)
1081*0Sstevel@tonic-gate	MKIVCT(55)
1082*0Sstevel@tonic-gate	MKIVCT(56)
1083*0Sstevel@tonic-gate	MKIVCT(57)
1084*0Sstevel@tonic-gate	MKIVCT(58)
1085*0Sstevel@tonic-gate	MKIVCT(59)
1086*0Sstevel@tonic-gate	MKIVCT(60)
1087*0Sstevel@tonic-gate	MKIVCT(61)
1088*0Sstevel@tonic-gate	MKIVCT(62)
1089*0Sstevel@tonic-gate	MKIVCT(63)
1090*0Sstevel@tonic-gate	MKIVCT(64)
1091*0Sstevel@tonic-gate	MKIVCT(65)
1092*0Sstevel@tonic-gate	MKIVCT(66)
1093*0Sstevel@tonic-gate	MKIVCT(67)
1094*0Sstevel@tonic-gate	MKIVCT(68)
1095*0Sstevel@tonic-gate	MKIVCT(69)
1096*0Sstevel@tonic-gate	MKIVCT(70)
1097*0Sstevel@tonic-gate	MKIVCT(71)
1098*0Sstevel@tonic-gate	MKIVCT(72)
1099*0Sstevel@tonic-gate	MKIVCT(73)
1100*0Sstevel@tonic-gate	MKIVCT(74)
1101*0Sstevel@tonic-gate	MKIVCT(75)
1102*0Sstevel@tonic-gate	MKIVCT(76)
1103*0Sstevel@tonic-gate	MKIVCT(77)
1104*0Sstevel@tonic-gate	MKIVCT(78)
1105*0Sstevel@tonic-gate	MKIVCT(79)
1106*0Sstevel@tonic-gate	MKIVCT(80)
1107*0Sstevel@tonic-gate	MKIVCT(81)
1108*0Sstevel@tonic-gate	MKIVCT(82)
1109*0Sstevel@tonic-gate	MKIVCT(83)
1110*0Sstevel@tonic-gate	MKIVCT(84)
1111*0Sstevel@tonic-gate	MKIVCT(85)
1112*0Sstevel@tonic-gate	MKIVCT(86)
1113*0Sstevel@tonic-gate	MKIVCT(87)
1114*0Sstevel@tonic-gate	MKIVCT(88)
1115*0Sstevel@tonic-gate	MKIVCT(89)
1116*0Sstevel@tonic-gate	MKIVCT(90)
1117*0Sstevel@tonic-gate	MKIVCT(91)
1118*0Sstevel@tonic-gate	MKIVCT(92)
1119*0Sstevel@tonic-gate	MKIVCT(93)
1120*0Sstevel@tonic-gate	MKIVCT(94)
1121*0Sstevel@tonic-gate	MKIVCT(95)
1122*0Sstevel@tonic-gate	MKIVCT(96)
1123*0Sstevel@tonic-gate	MKIVCT(97)
1124*0Sstevel@tonic-gate	MKIVCT(98)
1125*0Sstevel@tonic-gate	MKIVCT(99)
1126*0Sstevel@tonic-gate	MKIVCT(100)
1127*0Sstevel@tonic-gate	MKIVCT(101)
1128*0Sstevel@tonic-gate	MKIVCT(102)
1129*0Sstevel@tonic-gate	MKIVCT(103)
1130*0Sstevel@tonic-gate	MKIVCT(104)
1131*0Sstevel@tonic-gate	MKIVCT(105)
1132*0Sstevel@tonic-gate	MKIVCT(106)
1133*0Sstevel@tonic-gate	MKIVCT(107)
1134*0Sstevel@tonic-gate	MKIVCT(108)
1135*0Sstevel@tonic-gate	MKIVCT(109)
1136*0Sstevel@tonic-gate	MKIVCT(110)
1137*0Sstevel@tonic-gate	MKIVCT(111)
1138*0Sstevel@tonic-gate	MKIVCT(112)
1139*0Sstevel@tonic-gate	MKIVCT(113)
1140*0Sstevel@tonic-gate	MKIVCT(114)
1141*0Sstevel@tonic-gate	MKIVCT(115)
1142*0Sstevel@tonic-gate	MKIVCT(116)
1143*0Sstevel@tonic-gate	MKIVCT(117)
1144*0Sstevel@tonic-gate	MKIVCT(118)
1145*0Sstevel@tonic-gate	MKIVCT(119)
1146*0Sstevel@tonic-gate	MKIVCT(120)
1147*0Sstevel@tonic-gate	MKIVCT(121)
1148*0Sstevel@tonic-gate	MKIVCT(122)
1149*0Sstevel@tonic-gate	MKIVCT(123)
1150*0Sstevel@tonic-gate	MKIVCT(124)
1151*0Sstevel@tonic-gate	MKIVCT(125)
1152*0Sstevel@tonic-gate	MKIVCT(126)
1153*0Sstevel@tonic-gate	MKIVCT(127)
1154*0Sstevel@tonic-gate	MKIVCT(128)
1155*0Sstevel@tonic-gate	MKIVCT(129)
1156*0Sstevel@tonic-gate	MKIVCT(130)
1157*0Sstevel@tonic-gate	MKIVCT(131)
1158*0Sstevel@tonic-gate	MKIVCT(132)
1159*0Sstevel@tonic-gate	MKIVCT(133)
1160*0Sstevel@tonic-gate	MKIVCT(134)
1161*0Sstevel@tonic-gate	MKIVCT(135)
1162*0Sstevel@tonic-gate	MKIVCT(136)
1163*0Sstevel@tonic-gate	MKIVCT(137)
1164*0Sstevel@tonic-gate	MKIVCT(138)
1165*0Sstevel@tonic-gate	MKIVCT(139)
1166*0Sstevel@tonic-gate	MKIVCT(140)
1167*0Sstevel@tonic-gate	MKIVCT(141)
1168*0Sstevel@tonic-gate	MKIVCT(142)
1169*0Sstevel@tonic-gate	MKIVCT(143)
1170*0Sstevel@tonic-gate	MKIVCT(144)
1171*0Sstevel@tonic-gate	MKIVCT(145)
1172*0Sstevel@tonic-gate	MKIVCT(146)
1173*0Sstevel@tonic-gate	MKIVCT(147)
1174*0Sstevel@tonic-gate	MKIVCT(148)
1175*0Sstevel@tonic-gate	MKIVCT(149)
1176*0Sstevel@tonic-gate	MKIVCT(150)
1177*0Sstevel@tonic-gate	MKIVCT(151)
1178*0Sstevel@tonic-gate	MKIVCT(152)
1179*0Sstevel@tonic-gate	MKIVCT(153)
1180*0Sstevel@tonic-gate	MKIVCT(154)
1181*0Sstevel@tonic-gate	MKIVCT(155)
1182*0Sstevel@tonic-gate	MKIVCT(156)
1183*0Sstevel@tonic-gate	MKIVCT(157)
1184*0Sstevel@tonic-gate	MKIVCT(158)
1185*0Sstevel@tonic-gate	MKIVCT(159)
1186*0Sstevel@tonic-gate	MKIVCT(160)
1187*0Sstevel@tonic-gate	MKIVCT(161)
1188*0Sstevel@tonic-gate	MKIVCT(162)
1189*0Sstevel@tonic-gate	MKIVCT(163)
1190*0Sstevel@tonic-gate	MKIVCT(164)
1191*0Sstevel@tonic-gate	MKIVCT(165)
1192*0Sstevel@tonic-gate	MKIVCT(166)
1193*0Sstevel@tonic-gate	MKIVCT(167)
1194*0Sstevel@tonic-gate	MKIVCT(168)
1195*0Sstevel@tonic-gate	MKIVCT(169)
1196*0Sstevel@tonic-gate	MKIVCT(170)
1197*0Sstevel@tonic-gate	MKIVCT(171)
1198*0Sstevel@tonic-gate	MKIVCT(172)
1199*0Sstevel@tonic-gate	MKIVCT(173)
1200*0Sstevel@tonic-gate	MKIVCT(174)
1201*0Sstevel@tonic-gate	MKIVCT(175)
1202*0Sstevel@tonic-gate	MKIVCT(176)
1203*0Sstevel@tonic-gate	MKIVCT(177)
1204*0Sstevel@tonic-gate	MKIVCT(178)
1205*0Sstevel@tonic-gate	MKIVCT(179)
1206*0Sstevel@tonic-gate	MKIVCT(180)
1207*0Sstevel@tonic-gate	MKIVCT(181)
1208*0Sstevel@tonic-gate	MKIVCT(182)
1209*0Sstevel@tonic-gate	MKIVCT(183)
1210*0Sstevel@tonic-gate	MKIVCT(184)
1211*0Sstevel@tonic-gate	MKIVCT(185)
1212*0Sstevel@tonic-gate	MKIVCT(186)
1213*0Sstevel@tonic-gate	MKIVCT(187)
1214*0Sstevel@tonic-gate	MKIVCT(188)
1215*0Sstevel@tonic-gate	MKIVCT(189)
1216*0Sstevel@tonic-gate	MKIVCT(190)
1217*0Sstevel@tonic-gate	MKIVCT(191)
1218*0Sstevel@tonic-gate	MKIVCT(192)
1219*0Sstevel@tonic-gate	MKIVCT(193)
1220*0Sstevel@tonic-gate	MKIVCT(194)
1221*0Sstevel@tonic-gate	MKIVCT(195)
1222*0Sstevel@tonic-gate	MKIVCT(196)
1223*0Sstevel@tonic-gate	MKIVCT(197)
1224*0Sstevel@tonic-gate	MKIVCT(198)
1225*0Sstevel@tonic-gate	MKIVCT(199)
1226*0Sstevel@tonic-gate	MKIVCT(200)
1227*0Sstevel@tonic-gate	MKIVCT(201)
1228*0Sstevel@tonic-gate	MKIVCT(202)
1229*0Sstevel@tonic-gate	MKIVCT(203)
1230*0Sstevel@tonic-gate	MKIVCT(204)
1231*0Sstevel@tonic-gate	MKIVCT(205)
1232*0Sstevel@tonic-gate	MKIVCT(206)
1233*0Sstevel@tonic-gate	MKIVCT(207)
1234*0Sstevel@tonic-gate	MKIVCT(208)
1235*0Sstevel@tonic-gate	MKIVCT(209)
1236*0Sstevel@tonic-gate	MKIVCT(210)
1237*0Sstevel@tonic-gate	MKIVCT(211)
1238*0Sstevel@tonic-gate	MKIVCT(212)
1239*0Sstevel@tonic-gate	MKIVCT(213)
1240*0Sstevel@tonic-gate	MKIVCT(214)
1241*0Sstevel@tonic-gate	MKIVCT(215)
1242*0Sstevel@tonic-gate	MKIVCT(216)
1243*0Sstevel@tonic-gate	MKIVCT(217)
1244*0Sstevel@tonic-gate	MKIVCT(218)
1245*0Sstevel@tonic-gate	MKIVCT(219)
1246*0Sstevel@tonic-gate	MKIVCT(220)
1247*0Sstevel@tonic-gate	MKIVCT(221)
1248*0Sstevel@tonic-gate	MKIVCT(222)
1249*0Sstevel@tonic-gate	MKIVCT(223)
1250*0Sstevel@tonic-gate	MKIVCT(224)
1251*0Sstevel@tonic-gate	MKIVCT(225)
1252*0Sstevel@tonic-gate	MKIVCT(226)
1253*0Sstevel@tonic-gate	MKIVCT(227)
1254*0Sstevel@tonic-gate	MKIVCT(228)
1255*0Sstevel@tonic-gate	MKIVCT(229)
1256*0Sstevel@tonic-gate	MKIVCT(230)
1257*0Sstevel@tonic-gate	MKIVCT(231)
1258*0Sstevel@tonic-gate	MKIVCT(232)
1259*0Sstevel@tonic-gate	MKIVCT(233)
1260*0Sstevel@tonic-gate	MKIVCT(234)
1261*0Sstevel@tonic-gate	MKIVCT(235)
1262*0Sstevel@tonic-gate	MKIVCT(236)
1263*0Sstevel@tonic-gate	MKIVCT(237)
1264*0Sstevel@tonic-gate	MKIVCT(238)
1265*0Sstevel@tonic-gate	MKIVCT(239)
1266*0Sstevel@tonic-gate	MKIVCT(240)
1267*0Sstevel@tonic-gate	MKIVCT(241)
1268*0Sstevel@tonic-gate	MKIVCT(242)
1269*0Sstevel@tonic-gate	MKIVCT(243)
1270*0Sstevel@tonic-gate	MKIVCT(244)
1271*0Sstevel@tonic-gate	MKIVCT(245)
1272*0Sstevel@tonic-gate	MKIVCT(246)
1273*0Sstevel@tonic-gate	MKIVCT(247)
1274*0Sstevel@tonic-gate	MKIVCT(248)
1275*0Sstevel@tonic-gate	MKIVCT(249)
1276*0Sstevel@tonic-gate	MKIVCT(250)
1277*0Sstevel@tonic-gate	MKIVCT(251)
1278*0Sstevel@tonic-gate	MKIVCT(252)
1279*0Sstevel@tonic-gate	MKIVCT(253)
1280*0Sstevel@tonic-gate	MKIVCT(254)
1281*0Sstevel@tonic-gate	MKIVCT(255)
1282*0Sstevel@tonic-gate
1283*0Sstevel@tonic-gate#endif	/* __lint */
1284