xref: /titanic_41/usr/src/uts/intel/kdi/amd64/kdi_asm.s (revision 51208d123c034a24326c8a1bfc3b557a63d467e8)
1/*
2 * CDDL HEADER START
3 *
4 * The contents of this file are subject to the terms of the
5 * Common Development and Distribution License (the "License").
6 * You may not use this file except in compliance with the License.
7 *
8 * You can obtain a copy of the license at usr/src/OPENSOLARIS.LICENSE
9 * or http://www.opensolaris.org/os/licensing.
10 * See the License for the specific language governing permissions
11 * and limitations under the License.
12 *
13 * When distributing Covered Code, include this CDDL HEADER in each
14 * file and include the License file at usr/src/OPENSOLARIS.LICENSE.
15 * If applicable, add the following below this CDDL HEADER, with the
16 * fields enclosed by brackets "[]" replaced with your own identifying
17 * information: Portions Copyright [yyyy] [name of copyright owner]
18 *
19 * CDDL HEADER END
20 */
21
22/*
23 * Copyright 2007 Sun Microsystems, Inc.  All rights reserved.
24 * Use is subject to license terms.
25 */
26
27#pragma ident	"%Z%%M%	%I%	%E% SMI"
28
29/*
30 * Debugger entry for both master and slave CPUs
31 */
32
33#if defined(__lint)
34#include <sys/types.h>
35#endif
36
37#include <sys/segments.h>
38#include <sys/asm_linkage.h>
39#include <sys/controlregs.h>
40#include <sys/x86_archext.h>
41#include <sys/privregs.h>
42#include <sys/machprivregs.h>
43#include <sys/kdi_regs.h>
44#include <sys/psw.h>
45#include <sys/uadmin.h>
46
47#ifdef _ASM
48
49#include <kdi_assym.h>
50#include <assym.h>
51
52/* clobbers %rdx, %rcx, returns addr in %rax, CPU ID in %rbx */
53#define	GET_CPUSAVE_ADDR \
54	movzbq	%gs:CPU_ID, %rbx;		\
55	movq	%rbx, %rax;			\
56	movq	$KRS_SIZE, %rcx;		\
57	mulq	%rcx;				\
58	movq	$kdi_cpusave, %rdx;		\
59	/*CSTYLED*/				\
60	addq	(%rdx), %rax
61
62/*
63 * Save copies of the IDT and GDT descriptors.  Note that we only save the IDT
64 * and GDT if the IDT isn't ours, as we may be legitimately re-entering the
65 * debugger through the trap handler.  We don't want to clobber the saved IDT
66 * in the process, as we'd end up resuming the world on our IDT.
67 */
68#define	SAVE_IDTGDT				\
69	movq	%gs:CPU_IDT, %r11;		\
70	leaq    kdi_idt(%rip), %rsi;		\
71	cmpq	%rsi, %r11;			\
72	je	1f;				\
73	movq	%r11, KRS_IDT(%rax);		\
74	movq	%gs:CPU_GDT, %r11;		\
75	movq	%r11, KRS_GDT(%rax);		\
761:
77
78/* %ss, %rsp, %rflags, %cs, %rip, %err, %trapno already on stack */
79
80#define	KDI_SAVE_REGS(base) \
81	movq	%rdi, REG_OFF(KDIREG_RDI)(base);	\
82	movq	%rsi, REG_OFF(KDIREG_RSI)(base);	\
83	movq	%rdx, REG_OFF(KDIREG_RDX)(base);	\
84	movq	%rcx, REG_OFF(KDIREG_RCX)(base);	\
85	movq	%r8, REG_OFF(KDIREG_R8)(base);		\
86	movq	%r9, REG_OFF(KDIREG_R9)(base);		\
87	movq	%rax, REG_OFF(KDIREG_RAX)(base);	\
88	movq	%rbx, REG_OFF(KDIREG_RBX)(base);	\
89	movq	%rbp, REG_OFF(KDIREG_RBP)(base);	\
90	movq	%r10, REG_OFF(KDIREG_R10)(base);	\
91	movq	%r11, REG_OFF(KDIREG_R11)(base);	\
92	movq	%r12, REG_OFF(KDIREG_R12)(base);	\
93	movq	%r13, REG_OFF(KDIREG_R13)(base);	\
94	movq	%r14, REG_OFF(KDIREG_R14)(base);	\
95	movq	%r15, REG_OFF(KDIREG_R15)(base);	\
96	movq	%rbp, REG_OFF(KDIREG_SAVFP)(base);	\
97	movq	REG_OFF(KDIREG_RIP)(base), %rax;	\
98	movq	%rax, REG_OFF(KDIREG_SAVPC)(base);	\
99	clrq	%rax;					\
100	movw	%ds, %ax;				\
101	movq	%rax, REG_OFF(KDIREG_DS)(base);		\
102	movw	%es, %ax;				\
103	movq	%rax, REG_OFF(KDIREG_ES)(base);		\
104	movw	%fs, %ax;				\
105	movq	%rax, REG_OFF(KDIREG_FS)(base);		\
106	movw	%gs, %ax;				\
107	movq	%rax, REG_OFF(KDIREG_GS)(base)
108
109#define	KDI_RESTORE_REGS(base) \
110	movq	base, %rdi;				\
111	movq	REG_OFF(KDIREG_ES)(%rdi), %rax;		\
112	movw	%ax, %es;				\
113	movq	REG_OFF(KDIREG_DS)(%rdi), %rax;		\
114	movw	%ax, %ds;				\
115	movq	REG_OFF(KDIREG_R15)(%rdi), %r15;	\
116	movq	REG_OFF(KDIREG_R14)(%rdi), %r14;	\
117	movq	REG_OFF(KDIREG_R13)(%rdi), %r13;	\
118	movq	REG_OFF(KDIREG_R12)(%rdi), %r12;	\
119	movq	REG_OFF(KDIREG_R11)(%rdi), %r11;	\
120	movq	REG_OFF(KDIREG_R10)(%rdi), %r10;	\
121	movq	REG_OFF(KDIREG_RBP)(%rdi), %rbp;	\
122	movq	REG_OFF(KDIREG_RBX)(%rdi), %rbx;	\
123	movq	REG_OFF(KDIREG_RAX)(%rdi), %rax;	\
124	movq	REG_OFF(KDIREG_R9)(%rdi), %r9;		\
125	movq	REG_OFF(KDIREG_R8)(%rdi), %r8;		\
126	movq	REG_OFF(KDIREG_RCX)(%rdi), %rcx;	\
127	movq	REG_OFF(KDIREG_RDX)(%rdi), %rdx;	\
128	movq	REG_OFF(KDIREG_RSI)(%rdi), %rsi;	\
129	movq	REG_OFF(KDIREG_RDI)(%rdi), %rdi
130
131/*
132 * Each cpusave buffer has an area set aside for a ring buffer of breadcrumbs.
133 * The following macros manage the buffer.
134 */
135
136/* Advance the ring buffer */
137#define	ADVANCE_CRUMB_POINTER(cpusave, tmp1, tmp2) \
138	movq	KRS_CURCRUMBIDX(cpusave), tmp1;	\
139	cmpq	$[KDI_NCRUMBS - 1], tmp1;	\
140	jge	1f;				\
141	/* Advance the pointer and index */	\
142	addq	$1, tmp1;			\
143	movq	tmp1, KRS_CURCRUMBIDX(cpusave);	\
144	movq	KRS_CURCRUMB(cpusave), tmp1;	\
145	addq	$KRM_SIZE, tmp1;		\
146	jmp	2f;				\
1471:	/* Reset the pointer and index */	\
148	movq	$0, KRS_CURCRUMBIDX(cpusave);	\
149	leaq	KRS_CRUMBS(cpusave), tmp1;	\
1502:	movq	tmp1, KRS_CURCRUMB(cpusave);	\
151	/* Clear the new crumb */		\
152	movq	$KDI_NCRUMBS, tmp2;		\
1533:	movq	$0, -4(tmp1, tmp2, 4);		\
154	decq	tmp2;				\
155	jnz	3b
156
157/* Set a value in the current breadcrumb buffer */
158#define	ADD_CRUMB(cpusave, offset, value, tmp) \
159	movq	KRS_CURCRUMB(cpusave), tmp;	\
160	movq	value, offset(tmp)
161
162#endif	/* _ASM */
163
164/*
165 * The main entry point for master CPUs.  It also serves as the trap handler
166 * for all traps and interrupts taken during single-step.
167 */
168#if defined(__lint)
169void
170kdi_cmnint(void)
171{
172}
173#else	/* __lint */
174
175	/* XXX implement me */
176	ENTRY_NP(kdi_nmiint)
177	clrq	%rcx
178	movq	(%rcx), %rcx
179	SET_SIZE(kdi_nmiint)
180
181	ENTRY_NP(kdi_cmnint)
182	ALTENTRY(kdi_master_entry)
183
184	pushq	%rax
185	CLI(%rax)
186	popq	%rax
187
188	/* Save current register state */
189	subq	$REG_OFF(KDIREG_TRAPNO), %rsp
190	KDI_SAVE_REGS(%rsp)
191
192	/*
193	 * Switch to the kernel's GSBASE.  Neither GSBASE nor the ill-named
194	 * KGSBASE can be trusted, as the kernel may or may not have already
195	 * done a swapgs.  All is not lost, as the kernel can divine the correct
196	 * value for us.
197	 */
198	subq	$10, %rsp
199	sgdt	(%rsp)
200	movq	2(%rsp), %rdi	/* gdt base now in %rdi */
201	addq	$10, %rsp
202	call	kdi_gdt2gsbase	/* returns kernel's GSBASE in %rax */
203
204	movq	%rax, %rdx
205	shrq	$32, %rdx
206	movl	$MSR_AMD_GSBASE, %ecx
207	wrmsr
208
209	GET_CPUSAVE_ADDR	/* %rax = cpusave, %rbx = CPU ID */
210
211	ADVANCE_CRUMB_POINTER(%rax, %rcx, %rdx)
212
213	ADD_CRUMB(%rax, KRM_CPU_STATE, $KDI_CPU_STATE_MASTER, %rdx)
214
215	movq	REG_OFF(KDIREG_RIP)(%rsp), %rcx
216	ADD_CRUMB(%rax, KRM_PC, %rcx, %rdx)
217	ADD_CRUMB(%rax, KRM_SP, %rsp, %rdx)
218	movq	REG_OFF(KDIREG_TRAPNO)(%rsp), %rcx
219	ADD_CRUMB(%rax, KRM_TRAPNO, %rcx, %rdx)
220
221	movq	%rsp, %rbp
222	pushq	%rax
223
224	/*
225	 * Were we in the debugger when we took the trap (i.e. was %esp in one
226	 * of the debugger's memory ranges)?
227	 */
228	leaq	kdi_memranges, %rcx
229	movl	kdi_nmemranges, %edx
2301:	cmpq	MR_BASE(%rcx), %rsp
231	jl	2f		/* below this range -- try the next one */
232	cmpq	MR_LIM(%rcx), %rsp
233	jg	2f		/* above this range -- try the next one */
234	jmp	3f		/* matched within this range */
235
2362:	decl	%edx
237	jz	kdi_save_common_state	/* %rsp not within debugger memory */
238	addq	$MR_SIZE, %rcx
239	jmp	1b
240
2413:	/*
242	 * The master is still set.  That should only happen if we hit a trap
243	 * while running in the debugger.  Note that it may be an intentional
244	 * fault.  kmdb_dpi_handle_fault will sort it all out.
245	 */
246
247	movq	REG_OFF(KDIREG_TRAPNO)(%rbp), %rdi
248	movq	REG_OFF(KDIREG_RIP)(%rbp), %rsi
249	movq	REG_OFF(KDIREG_RSP)(%rbp), %rdx
250	movq	%rbx, %rcx		/* cpuid */
251
252	call	kdi_dvec_handle_fault
253
254	/*
255	 * If we're here, we ran into a debugger problem, and the user
256	 * elected to solve it by having the debugger debug itself.  The
257	 * state we're about to save is that of the debugger when it took
258	 * the fault.
259	 */
260
261	jmp	kdi_save_common_state
262
263	SET_SIZE(kdi_master_entry)
264	SET_SIZE(kdi_cmnint)
265
266#endif	/* __lint */
267
268/*
269 * The cross-call handler for slave CPUs.
270 *
271 * The debugger is single-threaded, so only one CPU, called the master, may be
272 * running it at any given time.  The other CPUs, known as slaves, spin in a
273 * busy loop until there's something for them to do.  This is the entry point
274 * for the slaves - they'll be sent here in response to a cross-call sent by the
275 * master.
276 */
277
278#if defined(__lint)
279char kdi_slave_entry_patch;
280
281void
282kdi_slave_entry(void)
283{
284}
285#else /* __lint */
286	.globl	kdi_slave_entry_patch;
287
288	ENTRY_NP(kdi_slave_entry)
289
290	/* kdi_msr_add_clrentry knows where this is */
291kdi_slave_entry_patch:
292	KDI_MSR_PATCH;
293
294	/*
295	 * Cross calls are implemented as function calls, so our stack currently
296	 * looks like one you'd get from a zero-argument function call.  That
297	 * is, there's the return %rip at %rsp, and that's about it.  We need
298	 * to make it look like an interrupt stack.  When we first save, we'll
299	 * reverse the saved %ss and %rip, which we'll fix back up when we've
300	 * freed up some general-purpose registers.  We'll also need to fix up
301	 * the saved %rsp.
302	 */
303
304	pushq	%rsp		/* pushed value off by 8 */
305	pushfq
306	CLI(%rax)
307	pushq	$KCS_SEL
308	clrq	%rax
309	movw	%ss, %ax
310	pushq	%rax		/* rip should be here */
311	pushq	$-1		/* phony trap error code */
312	pushq	$-1		/* phony trap number */
313
314	subq	$REG_OFF(KDIREG_TRAPNO), %rsp
315	KDI_SAVE_REGS(%rsp)
316
317	movq	REG_OFF(KDIREG_SS)(%rsp), %rax
318	xchgq	REG_OFF(KDIREG_RIP)(%rsp), %rax
319	movq	%rax, REG_OFF(KDIREG_SS)(%rsp)
320
321	movq	REG_OFF(KDIREG_RSP)(%rsp), %rax
322	addq	$8, %rax
323	movq	%rax, REG_OFF(KDIREG_RSP)(%rsp)
324
325	/*
326	 * We've saved all of the general-purpose registers, and have a stack
327	 * that is irettable (after we strip down to the error code)
328	 */
329
330	GET_CPUSAVE_ADDR	/* %rax = cpusave, %rbx = CPU ID */
331
332	ADVANCE_CRUMB_POINTER(%rax, %rcx, %rdx)
333
334	ADD_CRUMB(%rax, KRM_CPU_STATE, $KDI_CPU_STATE_SLAVE, %rdx)
335
336	movq	REG_OFF(KDIREG_RIP)(%rsp), %rcx
337	ADD_CRUMB(%rax, KRM_PC, %rcx, %rdx)
338
339	pushq	%rax
340	jmp	kdi_save_common_state
341
342	SET_SIZE(kdi_slave_entry)
343
344#endif	/* __lint */
345
346#if !defined(__lint)
347
348	ENTRY_NP(kdi_save_common_state)
349
350	/*
351	 * The state of the world:
352	 *
353	 * The stack has a complete set of saved registers and segment
354	 * selectors, arranged in the kdi_regs.h order.  It also has a pointer
355	 * to our cpusave area.
356	 *
357	 * We need to save, into the cpusave area, a pointer to these saved
358	 * registers.  After that, we save a few more registers, ready the
359	 * machine for debugger entry, and enter the debugger.
360	 */
361
362	popq	%rax			/* the cpusave area */
363	movq	%rsp, KRS_GREGS(%rax)	/* save ptr to current saved regs */
364
365	SAVE_IDTGDT
366
367	/* Save off %cr0, and clear write protect */
368	movq	%cr0, %rcx
369	movq	%rcx, KRS_CR0(%rax)
370	andq	$_BITNOT(CR0_WP), %rcx
371	movq	%rcx, %cr0
372
373	/* Save the debug registers and disable any active watchpoints */
374
375	movq	%rax, %r15		/* save cpusave area ptr */
376	movl	$7, %edi
377	call	kdi_dreg_get
378	movq	%rax, KRS_DRCTL(%r15)
379
380	andq	$_BITNOT(KDIREG_DRCTL_WPALLEN_MASK), %rax
381	movq	%rax, %rsi
382	movl	$7, %edi
383	call	kdi_dreg_set
384
385	movl	$6, %edi
386	call	kdi_dreg_get
387	movq	%rax, KRS_DRSTAT(%r15)
388
389	movl	$0, %edi
390	call	kdi_dreg_get
391	movq	%rax, KRS_DROFF(0)(%r15)
392
393	movl	$1, %edi
394	call	kdi_dreg_get
395	movq	%rax, KRS_DROFF(1)(%r15)
396
397	movl	$2, %edi
398	call	kdi_dreg_get
399	movq	%rax, KRS_DROFF(2)(%r15)
400
401	movl	$3, %edi
402	call	kdi_dreg_get
403	movq	%rax, KRS_DROFF(3)(%r15)
404
405	movq	%r15, %rax	/* restore cpu save area to rax */
406
407	/*
408	 * Save any requested MSRs.
409	 */
410	movq	KRS_MSR(%rax), %rcx
411	cmpq	$0, %rcx
412	je	no_msr
413
414	pushq	%rax		/* rdmsr clobbers %eax */
415	movq	%rcx, %rbx
416
4171:
418	movl	MSR_NUM(%rbx), %ecx
419	cmpl	$0, %ecx
420	je	msr_done
421
422	movl	MSR_TYPE(%rbx), %edx
423	cmpl	$KDI_MSR_READ, %edx
424	jne	msr_next
425
426	rdmsr			/* addr in %ecx, value into %edx:%eax */
427	movl	%eax, MSR_VAL(%rbx)
428	movl	%edx, _CONST(MSR_VAL + 4)(%rbx)
429
430msr_next:
431	addq	$MSR_SIZE, %rbx
432	jmp	1b
433
434msr_done:
435	popq	%rax
436
437no_msr:
438	clrq	%rbp		/* stack traces should end here */
439
440	pushq	%rax
441	movq	%rax, %rdi	/* cpusave */
442
443	call	kdi_debugger_entry
444
445	/* Pass cpusave and debugger return code for "call" to resume */
446	popq	%rdi
447	movq	%rax, %rsi
448
449	jmp	kdi_resume
450
451	SET_SIZE(kdi_save_common_state)
452
453#endif	/* !__lint */
454
455/*
456 * Given the address of the current CPU's cpusave area in %rax, the following
457 * macro restores the debugging state to said CPU.  Restored state includes
458 * the debug registers from the global %dr variables, and debugging MSRs from
459 * the CPU save area.  This code would be in a separate routine, but for the
460 * fact that some of the MSRs are jump-sensitive.  As such, we need to minimize
461 * the number of jumps taken subsequent to the update of said MSRs.  We can
462 * remove one jump (the ret) by using a macro instead of a function for the
463 * debugging state restoration code.
464 *
465 * Takes the cpusave area in %rdi as a parameter, clobbers %rax-%rdx
466 */
467#define	KDI_RESTORE_DEBUGGING_STATE \
468	pushq	%rdi;						\
469	leaq	kdi_drreg, %r15;				\
470	movl	$7, %edi;					\
471	movq	DR_CTL(%r15), %rsi;				\
472	call	kdi_dreg_set;					\
473								\
474	movl	$6, %edi;					\
475	movq	$KDIREG_DRSTAT_RESERVED, %rsi;			\
476	call	kdi_dreg_set;					\
477								\
478	movl	$0, %edi;					\
479	movq	DRADDR_OFF(0)(%r15), %rsi;			\
480	call	kdi_dreg_set;					\
481	movl	$1, %edi;					\
482	movq	DRADDR_OFF(1)(%r15), %rsi;			\
483	call	kdi_dreg_set;					\
484	movl	$2, %edi;					\
485	movq	DRADDR_OFF(2)(%r15), %rsi;			\
486	call	kdi_dreg_set;					\
487	movl	$3, %edi;					\
488	movq	DRADDR_OFF(3)(%r15), %rsi;			\
489	call	kdi_dreg_set;					\
490	popq	%rdi;						\
491								\
492	/*							\
493	 * Write any requested MSRs.				\
494	 */							\
495	movq	KRS_MSR(%rdi), %rbx;				\
496	cmpq	$0, %rbx;					\
497	je	3f;						\
4981:								\
499	movl	MSR_NUM(%rbx), %ecx;				\
500	cmpl	$0, %ecx;					\
501	je	3f;						\
502								\
503	movl	MSR_TYPE(%rbx), %edx;				\
504	cmpl	$KDI_MSR_WRITE, %edx;				\
505	jne	2f;						\
506								\
507	movq	MSR_VALP(%rbx), %rdx;				\
508	movl	0(%rdx), %eax;					\
509	movl	4(%rdx), %edx;					\
510	wrmsr;							\
5112:								\
512	addq	$MSR_SIZE, %rbx;				\
513	jmp	1b;						\
5143:								\
515	/*							\
516	 * We must not branch after re-enabling LBR.  If	\
517	 * kdi_wsr_wrexit_msr is set, it contains the number	\
518	 * of the MSR that controls LBR.  kdi_wsr_wrexit_valp	\
519	 * contains the value that is to be written to enable	\
520	 * LBR.							\
521	 */							\
522	movl	kdi_msr_wrexit_msr, %ecx;			\
523	cmpl	$0, %ecx;					\
524	je	1f;						\
525								\
526	movq	kdi_msr_wrexit_valp, %rdx;			\
527	movl	0(%rdx), %eax;					\
528	movl	4(%rdx), %edx;					\
529								\
530	wrmsr;							\
5311:
532
533#if defined(__lint)
534/*ARGSUSED*/
535void
536kdi_cpu_debug_init(kdi_cpusave_t *save)
537{
538}
539#else	/* __lint */
540
541	ENTRY_NP(kdi_cpu_debug_init)
542	pushq	%rbp
543	movq	%rsp, %rbp
544
545	pushq	%rbx		/* macro will clobber %rbx */
546	KDI_RESTORE_DEBUGGING_STATE
547	popq	%rbx
548
549	leave
550	ret
551
552	SET_SIZE(kdi_cpu_debug_init)
553#endif	/* !__lint */
554
555/*
556 * Resume the world.  The code that calls kdi_resume has already
557 * decided whether or not to restore the IDT.
558 */
559#if defined(__lint)
560void
561kdi_resume(void)
562{
563}
564#else	/* __lint */
565
566	ENTRY_NP(kdi_resume)
567
568	/* cpusave in %rdi, debugger command in %rsi */
569
570	cmpq	$KDI_RESUME_PASS_TO_KERNEL, %rsi
571	je	kdi_pass_to_kernel
572
573	/*
574	 * Send this CPU back into the world
575	 */
576	movq	KRS_CR0(%rdi), %rdx
577	movq	%rdx, %cr0
578
579	KDI_RESTORE_DEBUGGING_STATE
580
581	movq	KRS_GREGS(%rdi), %rsp
582	KDI_RESTORE_REGS(%rsp)
583	addq	$REG_OFF(KDIREG_RIP), %rsp	/* Discard state, trapno, err */
584	IRET
585	/*NOTREACHED*/
586	SET_SIZE(kdi_resume)
587
588#endif	/* __lint */
589
590#if !defined(__lint)
591
592	ENTRY_NP(kdi_pass_to_kernel)
593
594	/* cpusave is still in %rdi */
595	movq	KRS_CR0(%rdi), %rdx
596	movq	%rdx, %cr0
597
598	/*
599	 * When we replaced the kernel's handlers in the IDT, we made note of
600	 * the handlers being replaced, thus allowing us to pass traps directly
601	 * to said handlers here.  We won't have any registers available for use
602	 * after we start popping, and we know we're single-threaded here, so
603	 * we have to use a global to store the handler address.
604	 */
605	movq	KRS_GREGS(%rdi), %rsp
606	movq	REG_OFF(KDIREG_TRAPNO)(%rsp), %rdi
607	call	kdi_kernel_trap2hdlr
608	movq	%rax, kdi_kernel_handler
609
610	/*
611	 * The trap handler will expect the stack to be in trap order, with
612	 * %rip being the last entry.  Our stack is currently in kdi_regs.h
613	 * order, so we'll need to pop (and restore) our way back down.
614	 */
615	KDI_RESTORE_REGS(%rsp)
616	addq	$REG_OFF(KDIREG_RIP), %rsp	/* Discard state, trapno, err */
617
618	jmp	*%cs:kdi_kernel_handler
619	/*NOTREACHED*/
620
621	SET_SIZE(kdi_pass_to_kernel)
622
623	/*
624	 * Reboot the system.  This routine is to be called only by the master
625	 * CPU.
626	 */
627	ENTRY_NP(kdi_reboot)
628
629	movl	$AD_BOOT, %edi
630	movl	$A_SHUTDOWN, %esi
631	call	*psm_shutdownf
632
633	/*
634	 * psm_shutdown didn't work or it wasn't set, try pc_reset.
635	 */
636	call	pc_reset
637	/*NOTREACHED*/
638
639	SET_SIZE(kdi_reboot)
640
641#endif	/* !__lint */
642