1181641Skmacy/*-
2181641Skmacy * Copyright (c) 1989, 1990 William F. Jolitz.
3181641Skmacy * Copyright (c) 1990 The Regents of the University of California.
4181641Skmacy * All rights reserved.
5181641Skmacy *
6181641Skmacy * Redistribution and use in source and binary forms, with or without
7181641Skmacy * modification, are permitted provided that the following conditions
8181641Skmacy * are met:
9181641Skmacy * 1. Redistributions of source code must retain the above copyright
10181641Skmacy *    notice, this list of conditions and the following disclaimer.
11181641Skmacy * 2. Redistributions in binary form must reproduce the above copyright
12181641Skmacy *    notice, this list of conditions and the following disclaimer in the
13181641Skmacy *    documentation and/or other materials provided with the distribution.
14181641Skmacy * 4. Neither the name of the University nor the names of its contributors
15181641Skmacy *    may be used to endorse or promote products derived from this software
16181641Skmacy *    without specific prior written permission.
17181641Skmacy *
18181641Skmacy * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
19181641Skmacy * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
20181641Skmacy * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
21181641Skmacy * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
22181641Skmacy * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
23181641Skmacy * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
24181641Skmacy * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
25181641Skmacy * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
26181641Skmacy * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
27181641Skmacy * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
28181641Skmacy * SUCH DAMAGE.
29181641Skmacy *
30181641Skmacy * $FreeBSD$
31181641Skmacy */
32181641Skmacy
33181641Skmacy#include "opt_apic.h"
34181641Skmacy#include "opt_npx.h"
35181641Skmacy
36181641Skmacy#include <machine/asmacros.h>
37181641Skmacy#include <machine/psl.h>
38181641Skmacy#include <machine/trap.h>
39181641Skmacy
40181641Skmacy#include "assym.s"
41181641Skmacy
42181641Skmacy#define	SEL_RPL_MASK	0x0002
43181641Skmacy#define __HYPERVISOR_iret	23
44181641Skmacy
45181641Skmacy/* Offsets into shared_info_t. */
46184071Skmacy
47181641Skmacy#define evtchn_upcall_pending /* 0 */
48181641Skmacy#define evtchn_upcall_mask       1
49181641Skmacy
50184071Skmacy#define	sizeof_vcpu_shift	6
51184071Skmacy
52184071Skmacy
53184071Skmacy#ifdef SMP
54184198Skmacy#define GET_VCPU_INFO(reg)	movl PCPU(CPUID),reg			; \
55184071Skmacy				shl  $sizeof_vcpu_shift,reg		; \
56184071Skmacy				addl HYPERVISOR_shared_info,reg
57184071Skmacy#else
58184071Skmacy#define GET_VCPU_INFO(reg)	movl HYPERVISOR_shared_info,reg
59184071Skmacy#endif
60184071Skmacy
61184071Skmacy#define __DISABLE_INTERRUPTS(reg)	movb $1,evtchn_upcall_mask(reg)
62184071Skmacy#define __ENABLE_INTERRUPTS(reg)	movb $0,evtchn_upcall_mask(reg)
63184071Skmacy#define DISABLE_INTERRUPTS(reg)	GET_VCPU_INFO(reg)			; \
64184071Skmacy				__DISABLE_INTERRUPTS(reg)
65184071Skmacy#define ENABLE_INTERRUPTS(reg)	GET_VCPU_INFO(reg)			; \
66184071Skmacy				__ENABLE_INTERRUPTS(reg)
67184071Skmacy#define __TEST_PENDING(reg)	testb $0xFF,evtchn_upcall_pending(reg)
68184071Skmacy
69181641Skmacy#define POPA \
70181641Skmacy        popl %edi; \
71181641Skmacy        popl %esi; \
72181641Skmacy        popl %ebp; \
73181641Skmacy        popl %ebx; \
74181641Skmacy        popl %ebx; \
75181641Skmacy        popl %edx; \
76181641Skmacy        popl %ecx; \
77181641Skmacy        popl %eax;
78181641Skmacy
79181641Skmacy	.text
80181641Skmacy
81181641Skmacy/*****************************************************************************/
82181641Skmacy/* Trap handling                                                             */
83181641Skmacy/*****************************************************************************/
84181641Skmacy/*
85181641Skmacy * Trap and fault vector routines.
86181641Skmacy *
87181641Skmacy * Most traps are 'trap gates', SDT_SYS386TGT.  A trap gate pushes state on
88181641Skmacy * the stack that mostly looks like an interrupt, but does not disable
89181641Skmacy * interrupts.  A few of the traps we are use are interrupt gates,
90181641Skmacy * SDT_SYS386IGT, which are nearly the same thing except interrupts are
91181641Skmacy * disabled on entry.
92181641Skmacy *
93181641Skmacy * The cpu will push a certain amount of state onto the kernel stack for
94181641Skmacy * the current process.  The amount of state depends on the type of trap
95181641Skmacy * and whether the trap crossed rings or not.  See i386/include/frame.h.
96181641Skmacy * At the very least the current EFLAGS (status register, which includes
97181641Skmacy * the interrupt disable state prior to the trap), the code segment register,
98181641Skmacy * and the return instruction pointer are pushed by the cpu.  The cpu
99181641Skmacy * will also push an 'error' code for certain traps.  We push a dummy
100181641Skmacy * error code for those traps where the cpu doesn't in order to maintain
101181641Skmacy * a consistent frame.  We also push a contrived 'trap number'.
102181641Skmacy *
103181641Skmacy * The cpu does not push the general registers, we must do that, and we
104181641Skmacy * must restore them prior to calling 'iret'.  The cpu adjusts the %cs and
105181641Skmacy * %ss segment registers, but does not mess with %ds, %es, or %fs.  Thus we
106181641Skmacy * must load them with appropriate values for supervisor mode operation.
107181641Skmacy */
108181641Skmacy
109181641SkmacyMCOUNT_LABEL(user)
110181641SkmacyMCOUNT_LABEL(btrap)
111181641Skmacy
112181641Skmacy#define	TRAP(a)		pushl $(a) ; jmp alltraps
113181641Skmacy
114181641SkmacyIDTVEC(div)
115181641Skmacy	pushl $0; TRAP(T_DIVIDE)
116181641SkmacyIDTVEC(dbg)
117181641Skmacy	pushl $0; TRAP(T_TRCTRAP)
118181641SkmacyIDTVEC(nmi)
119181641Skmacy	pushl $0; TRAP(T_NMI)
120181641SkmacyIDTVEC(bpt)
121181641Skmacy	pushl $0; TRAP(T_BPTFLT)
122181641SkmacyIDTVEC(ofl)
123181641Skmacy	pushl $0; TRAP(T_OFLOW)
124181641SkmacyIDTVEC(bnd)
125181641Skmacy	pushl $0; TRAP(T_BOUND)
126181641SkmacyIDTVEC(ill)
127181641Skmacy	pushl $0; TRAP(T_PRIVINFLT)
128181641SkmacyIDTVEC(dna)
129181641Skmacy	pushl $0; TRAP(T_DNA)
130181641SkmacyIDTVEC(fpusegm)
131181641Skmacy	pushl $0; TRAP(T_FPOPFLT)
132181641SkmacyIDTVEC(tss)
133181641Skmacy	TRAP(T_TSSFLT)
134181641SkmacyIDTVEC(missing)
135181641Skmacy	TRAP(T_SEGNPFLT)
136181641SkmacyIDTVEC(stk)
137181641Skmacy	TRAP(T_STKFLT)
138181641SkmacyIDTVEC(prot)
139181641Skmacy	TRAP(T_PROTFLT)
140181641SkmacyIDTVEC(page)
141181641Skmacy	TRAP(T_PAGEFLT)
142181641SkmacyIDTVEC(mchk)
143181641Skmacy	pushl $0; TRAP(T_MCHK)
144181641SkmacyIDTVEC(rsvd)
145181641Skmacy	pushl $0; TRAP(T_RESERVED)
146181641SkmacyIDTVEC(fpu)
147181641Skmacy	pushl $0; TRAP(T_ARITHTRAP)
148181641SkmacyIDTVEC(align)
149181641Skmacy	TRAP(T_ALIGNFLT)
150181641SkmacyIDTVEC(xmm)
151181641Skmacy	pushl $0; TRAP(T_XMMFLT)
152181641Skmacy
153181641SkmacyIDTVEC(hypervisor_callback)
154181807Skmacy	pushl $0;
155181807Skmacy	pushl $0;
156181807Skmacy	pushal
157181807Skmacy	pushl	%ds
158181807Skmacy	pushl	%es
159181807Skmacy	pushl	%fs
160181807Skmacyupcall_with_regs_pushed:
161181807Skmacy	SET_KERNEL_SREGS
162181807Skmacy	FAKE_MCOUNT(TF_EIP(%esp))
163181807Skmacycall_evtchn_upcall:
164181807Skmacy	movl	TF_EIP(%esp),%eax
165181807Skmacy	cmpl	$scrit,%eax
166181807Skmacy	jb	10f
167181807Skmacy	cmpl	$ecrit,%eax
168181807Skmacy	jb	critical_region_fixup
169181807Skmacy
170181807Skmacy10:	pushl	%esp
171181807Skmacy	call	evtchn_do_upcall
172181807Skmacy	addl	$4,%esp
173181641Skmacy
174181807Skmacy	/*
175181807Skmacy	 * Return via doreti to handle ASTs.
176181807Skmacy	 */
177181807Skmacy	MEXITCOUNT
178181807Skmacy	jmp	doreti
179181807Skmacy
180181807Skmacy
181181641Skmacyhypervisor_callback_pending:
182184071Skmacy	DISABLE_INTERRUPTS(%esi)				/*	cli */
183181807Skmacy	jmp	10b
184181641Skmacy	/*
185181641Skmacy	 * alltraps entry point.  Interrupts are enabled if this was a trap
186181641Skmacy	 * gate (TGT), else disabled if this was an interrupt gate (IGT).
187181641Skmacy	 * Note that int0x80_syscall is a trap gate.  Only page faults
188181641Skmacy	 * use an interrupt gate.
189181641Skmacy	 */
190181641Skmacy	SUPERALIGN_TEXT
191181641Skmacy	.globl	alltraps
192181641Skmacy	.type	alltraps,@function
193181641Skmacyalltraps:
194181641Skmacy	pushal
195181641Skmacy	pushl	%ds
196181641Skmacy	pushl	%es
197181641Skmacy	pushl	%fs
198181641Skmacy
199181641Skmacyalltraps_with_regs_pushed:
200181641Skmacy	SET_KERNEL_SREGS
201181641Skmacy	FAKE_MCOUNT(TF_EIP(%esp))
202181807Skmacy
203181641Skmacycalltrap:
204181807Skmacy	push	%esp
205181641Skmacy	call	trap
206181641Skmacy	add	$4, %esp
207181641Skmacy
208181641Skmacy	/*
209181641Skmacy	 * Return via doreti to handle ASTs.
210181641Skmacy	 */
211181641Skmacy	MEXITCOUNT
212181641Skmacy	jmp	doreti
213181641Skmacy
214181641Skmacy/*
215181641Skmacy * SYSCALL CALL GATE (old entry point for a.out binaries)
216181641Skmacy *
217181641Skmacy * The intersegment call has been set up to specify one dummy parameter.
218181641Skmacy *
219181641Skmacy * This leaves a place to put eflags so that the call frame can be
220181641Skmacy * converted to a trap frame. Note that the eflags is (semi-)bogusly
221181641Skmacy * pushed into (what will be) tf_err and then copied later into the
222181641Skmacy * final spot. It has to be done this way because esp can't be just
223181641Skmacy * temporarily altered for the pushfl - an interrupt might come in
224181641Skmacy * and clobber the saved cs/eip.
225181641Skmacy */
226181641Skmacy	SUPERALIGN_TEXT
227181641SkmacyIDTVEC(lcall_syscall)
228181641Skmacy	pushfl				/* save eflags */
229181641Skmacy	popl	8(%esp)			/* shuffle into tf_eflags */
230181641Skmacy	pushl	$7			/* sizeof "lcall 7,0" */
231181641Skmacy	subl	$4,%esp			/* skip over tf_trapno */
232181641Skmacy	pushal
233181641Skmacy	pushl	%ds
234181641Skmacy	pushl	%es
235181641Skmacy	pushl	%fs
236181641Skmacy	SET_KERNEL_SREGS
237181641Skmacy	FAKE_MCOUNT(TF_EIP(%esp))
238181641Skmacy	pushl	%esp
239181641Skmacy	call	syscall
240181641Skmacy	add	$4, %esp
241181641Skmacy	MEXITCOUNT
242181641Skmacy	jmp	doreti
243181641Skmacy
244181641Skmacy/*
245181641Skmacy * Call gate entry for FreeBSD ELF and Linux/NetBSD syscall (int 0x80)
246181641Skmacy *
247181641Skmacy * Even though the name says 'int0x80', this is actually a TGT (trap gate)
248181641Skmacy * rather then an IGT (interrupt gate).  Thus interrupts are enabled on
249181641Skmacy * entry just as they are for a normal syscall.
250181641Skmacy */
251181641Skmacy	SUPERALIGN_TEXT
252181641SkmacyIDTVEC(int0x80_syscall)
253181641Skmacy	pushl	$2			/* sizeof "int 0x80" */
254181641Skmacy	pushl	$0xBEEF			/* for debug */
255181641Skmacy	pushal
256181641Skmacy	pushl	%ds
257181641Skmacy	pushl	%es
258181641Skmacy	pushl	%fs
259181641Skmacy	SET_KERNEL_SREGS
260181641Skmacy	FAKE_MCOUNT(TF_EIP(%esp))
261181641Skmacy	pushl	%esp
262181641Skmacy	call	syscall
263181641Skmacy	add	$4, %esp
264181641Skmacy	MEXITCOUNT
265181641Skmacy	jmp	doreti
266181641Skmacy
267181641SkmacyENTRY(fork_trampoline)
268181641Skmacy	pushl	%esp			/* trapframe pointer */
269181641Skmacy	pushl	%ebx			/* arg1 */
270181641Skmacy	pushl	%esi			/* function */
271181641Skmacy	call	fork_exit
272181641Skmacy	addl	$12,%esp
273181641Skmacy	/* cut from syscall */
274181641Skmacy
275181641Skmacy	/*
276181641Skmacy	 * Return via doreti to handle ASTs.
277181641Skmacy	 */
278181641Skmacy	MEXITCOUNT
279181641Skmacy	jmp	doreti
280181641Skmacy
281181641Skmacy
282181641Skmacy/*
283181641Skmacy * To efficiently implement classification of trap and interrupt handlers
284181641Skmacy * for profiling, there must be only trap handlers between the labels btrap
285181641Skmacy * and bintr, and only interrupt handlers between the labels bintr and
286181641Skmacy * eintr.  This is implemented (partly) by including files that contain
287181641Skmacy * some of the handlers.  Before including the files, set up a normal asm
288181641Skmacy * environment so that the included files doen't need to know that they are
289181641Skmacy * included.
290181641Skmacy */
291181641Skmacy
292181641Skmacy	.data
293181641Skmacy	.p2align 4
294181641Skmacy	.text
295181641Skmacy	SUPERALIGN_TEXT
296181641SkmacyMCOUNT_LABEL(bintr)
297181641Skmacy
298181641Skmacy#ifdef DEV_APIC
299181641Skmacy	.data
300181641Skmacy	.p2align 4
301181641Skmacy	.text
302181641Skmacy	SUPERALIGN_TEXT
303181641Skmacy
304181641Skmacy#include <i386/i386/apic_vector.s>
305181641Skmacy#endif
306181641Skmacy
307181641Skmacy	.data
308181641Skmacy	.p2align 4
309181641Skmacy	.text
310181641Skmacy	SUPERALIGN_TEXT
311181641Skmacy#include <i386/i386/vm86bios.s>
312181641Skmacy
313181641Skmacy	.text
314181641SkmacyMCOUNT_LABEL(eintr)
315181641Skmacy
316181641Skmacy/*
317181641Skmacy * void doreti(struct trapframe)
318181641Skmacy *
319181641Skmacy * Handle return from interrupts, traps and syscalls.
320181641Skmacy */
321181641Skmacy	.text
322181641Skmacy	SUPERALIGN_TEXT
323181641Skmacy	.type	doreti,@function
324181641Skmacydoreti:
325181641Skmacy	FAKE_MCOUNT($bintr)		/* init "from" bintr -> doreti */
326181641Skmacydoreti_next:
327181641Skmacy#ifdef notyet
328181641Skmacy	/*
329181641Skmacy	 * Check if ASTs can be handled now.  PSL_VM must be checked first
330181641Skmacy	 * since segment registers only have an RPL in non-VM86 mode.
331181641Skmacy	 */
332181641Skmacy	testl	$PSL_VM,TF_EFLAGS(%esp)	/* are we in vm86 mode? */
333181641Skmacy	jz	doreti_notvm86
334181641Skmacy	movl	PCPU(CURPCB),%ecx
335181641Skmacy	testl	$PCB_VM86CALL,PCB_FLAGS(%ecx)	/* are we in a vm86 call? */
336181641Skmacy	jz	doreti_ast		/* can handle ASTS now if not */
337181641Skmacy  	jmp	doreti_exit
338181641Skmacy
339181641Skmacydoreti_notvm86:
340181641Skmacy#endif
341181641Skmacy	testb	$SEL_RPL_MASK,TF_CS(%esp) /* are we returning to user mode? */
342181641Skmacy	jz	doreti_exit		/* can't handle ASTs now if not */
343181641Skmacy
344181641Skmacydoreti_ast:
345181641Skmacy	/*
346181641Skmacy	 * Check for ASTs atomically with returning.  Disabling CPU
347181641Skmacy	 * interrupts provides sufficient locking even in the SMP case,
348181641Skmacy	 * since we will be informed of any new ASTs by an IPI.
349181641Skmacy	 */
350184071Skmacy	DISABLE_INTERRUPTS(%esi)				/*	cli */
351181641Skmacy	movl	PCPU(CURTHREAD),%eax
352181641Skmacy	testl	$TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%eax)
353181641Skmacy	je	doreti_exit
354184071Skmacy	ENABLE_INTERRUPTS(%esi)	/* sti */
355181641Skmacy	pushl	%esp			/* pass a pointer to the trapframe */
356181641Skmacy	call	ast
357181641Skmacy	add	$4,%esp
358181641Skmacy	jmp	doreti_ast
359181641Skmacy
360181641Skmacy	/*
361181641Skmacy	 * doreti_exit:	pop registers, iret.
362181641Skmacy	 *
363181641Skmacy	 *	The segment register pop is a special case, since it may
364181641Skmacy	 *	fault if (for example) a sigreturn specifies bad segment
365181641Skmacy	 *	registers.  The fault is handled in trap.c.
366181641Skmacy	 */
367181641Skmacydoreti_exit:
368184071Skmacy	ENABLE_INTERRUPTS(%esi) # reenable event callbacks (sti)
369181641Skmacy
370181641Skmacy	.globl	scrit
371181641Skmacyscrit:
372184071Skmacy	__TEST_PENDING(%esi)
373181641Skmacy        jnz	hypervisor_callback_pending	/* More to go  */
374181641Skmacy
375181641Skmacy	MEXITCOUNT
376181641Skmacy
377181641Skmacy	.globl	doreti_popl_fs
378181641Skmacydoreti_popl_fs:
379181641Skmacy	popl	%fs
380181641Skmacy	.globl	doreti_popl_es
381181641Skmacydoreti_popl_es:
382181641Skmacy	popl	%es
383181641Skmacy	.globl	doreti_popl_ds
384181641Skmacydoreti_popl_ds:
385181641Skmacy	popl	%ds
386181641Skmacy
387181641Skmacy	/*
388181641Skmacy	 * This is important: as nothing is atomic over here (we can get
389181641Skmacy	 * interrupted any time), we use the critical_region_fixup() in
390181641Skmacy	 * order to figure out where out stack is. Therefore, do NOT use
391181641Skmacy	 * 'popal' here without fixing up the table!
392181641Skmacy	 */
393181641Skmacy	POPA
394181641Skmacy	addl	$8,%esp
395181641Skmacy	.globl	doreti_iret
396181641Skmacydoreti_iret:
397181641Skmacy	jmp	hypercall_page + (__HYPERVISOR_iret * 32)
398181641Skmacy	.globl	ecrit
399181641Skmacyecrit:
400181641Skmacy  	/*
401181641Skmacy	 * doreti_iret_fault and friends.  Alternative return code for
402181641Skmacy	 * the case where we get a fault in the doreti_exit code
403181641Skmacy	 * above.  trap() (i386/i386/trap.c) catches this specific
404181641Skmacy	 * case, sends the process a signal and continues in the
405181641Skmacy	 * corresponding place in the code below.
406181641Skmacy	 */
407181641Skmacy	ALIGN_TEXT
408181641Skmacy	.globl	doreti_iret_fault
409181641Skmacydoreti_iret_fault:
410181641Skmacy	subl	$8,%esp
411181641Skmacy	pushal
412181641Skmacy	pushl	%ds
413181641Skmacy	.globl	doreti_popl_ds_fault
414181641Skmacydoreti_popl_ds_fault:
415181641Skmacy	pushl	%es
416181641Skmacy	.globl	doreti_popl_es_fault
417181641Skmacydoreti_popl_es_fault:
418181641Skmacy	pushl	%fs
419181641Skmacy	.globl	doreti_popl_fs_fault
420181641Skmacydoreti_popl_fs_fault:
421181641Skmacy	movl	$0,TF_ERR(%esp)	/* XXX should be the error code */
422181641Skmacy	movl	$T_PROTFLT,TF_TRAPNO(%esp)
423181641Skmacy	jmp	alltraps_with_regs_pushed
424181641Skmacy
425181641Skmacy	/*
426181641Skmacy# [How we do the fixup]. We want to merge the current stack frame with the
427181641Skmacy# just-interrupted frame. How we do this depends on where in the critical
428181641Skmacy# region the interrupted handler was executing, and so how many saved
429181641Skmacy# registers are in each frame. We do this quickly using the lookup table
430181641Skmacy# 'critical_fixup_table'. For each byte offset in the critical region, it
431181641Skmacy# provides the number of bytes which have already been popped from the
432181641Skmacy# interrupted stack frame.
433181641Skmacy*/
434181641Skmacy
435181641Skmacy.globl critical_region_fixup
436181641Skmacycritical_region_fixup:
437181641Skmacy	addl $critical_fixup_table-scrit,%eax
438181641Skmacy	movzbl (%eax),%eax    # %eax contains num bytes popped
439181641Skmacy        movl  %esp,%esi
440181641Skmacy        add  %eax,%esi        # %esi points at end of src region
441181641Skmacy        movl  %esp,%edi
442181641Skmacy        add  $0x40,%edi       # %edi points at end of dst region
443181641Skmacy        movl  %eax,%ecx
444181641Skmacy        shr  $2,%ecx          # convert bytes to words
445181641Skmacy        je   16f              # skip loop if nothing to copy
446181641Skmacy15:     subl $4,%esi          # pre-decrementing copy loop
447181641Skmacy        subl $4,%edi
448181641Skmacy        movl (%esi),%eax
449181641Skmacy        movl %eax,(%edi)
450181641Skmacy        loop 15b
451181641Skmacy16:     movl %edi,%esp        # final %edi is top of merged stack
452181641Skmacy	jmp  hypervisor_callback_pending
453181641Skmacy
454181641Skmacy
455181641Skmacycritical_fixup_table:
456181641Skmacy.byte   0x0,0x0,0x0			#testb  $0x1,(%esi)
457181641Skmacy.byte   0x0,0x0,0x0,0x0,0x0,0x0		#jne    ea
458181641Skmacy.byte   0x0,0x0				#pop    %fs
459181641Skmacy.byte   0x04				#pop    %es
460181641Skmacy.byte   0x08				#pop    %ds
461181641Skmacy.byte   0x0c				#pop    %edi
462181641Skmacy.byte   0x10	                        #pop    %esi
463181641Skmacy.byte   0x14	                        #pop    %ebp
464181641Skmacy.byte   0x18	                        #pop    %ebx
465181641Skmacy.byte   0x1c	                        #pop    %ebx
466181641Skmacy.byte   0x20	                        #pop    %edx
467181641Skmacy.byte   0x24	                        #pop    %ecx
468181641Skmacy.byte   0x28	                        #pop    %eax
469181641Skmacy.byte   0x2c,0x2c,0x2c                  #add    $0x8,%esp
470181807Skmacy#if 0
471181807Skmacy	.byte   0x34	                        #iret
472181807Skmacy#endif
473181807Skmacy.byte   0x34,0x34,0x34,0x34,0x34        #HYPERVISOR_iret
474181641Skmacy
475181807Skmacy
476181641Skmacy/* # Hypervisor uses this for application faults while it executes.*/
477181641SkmacyENTRY(failsafe_callback)
478181641Skmacy	pushal
479181641Skmacy	call xen_failsafe_handler
480181641Skmacy/*#	call install_safe_pf_handler */
481181641Skmacy        movl 28(%esp),%ebx
482181641Skmacy1:      movl %ebx,%ds
483181641Skmacy        movl 32(%esp),%ebx
484181641Skmacy2:      movl %ebx,%es
485181641Skmacy        movl 36(%esp),%ebx
486181641Skmacy3:      movl %ebx,%fs
487181641Skmacy        movl 40(%esp),%ebx
488181641Skmacy4:      movl %ebx,%gs
489181641Skmacy/*#        call install_normal_pf_handler */
490181641Skmacy	popal
491181641Skmacy	addl $12,%esp
492181641Skmacy	iret
493181641Skmacy
494181641Skmacy
495