trap.c revision 1.78
1/*	$OpenBSD: trap.c,v 1.78 2004/06/17 00:30:08 mickey Exp $	*/
2
3/*
4 * Copyright (c) 1998-2004 Michael Shalayeff
5 * All rights reserved.
6 *
7 * Redistribution and use in source and binary forms, with or without
8 * modification, are permitted provided that the following conditions
9 * are met:
10 * 1. Redistributions of source code must retain the above copyright
11 *    notice, this list of conditions and the following disclaimer.
12 * 2. Redistributions in binary form must reproduce the above copyright
13 *    notice, this list of conditions and the following disclaimer in the
14 *    documentation and/or other materials provided with the distribution.
15 *
16 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
17 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
18 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
19 * IN NO EVENT SHALL THE AUTHOR OR HIS RELATIVES BE LIABLE FOR ANY DIRECT,
20 * INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
21 * (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
22 * SERVICES; LOSS OF MIND, USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
23 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
24 * STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING
25 * IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF
26 * THE POSSIBILITY OF SUCH DAMAGE.
27 */
28
29/* #define TRAPDEBUG */
30
31#include <sys/param.h>
32#include <sys/systm.h>
33#include <sys/syscall.h>
34#include <sys/ktrace.h>
35#include <sys/proc.h>
36#include <sys/signalvar.h>
37#include <sys/user.h>
38
39#include <net/netisr.h>
40
41#include "systrace.h"
42#include <dev/systrace.h>
43
44#include <uvm/uvm.h>
45
46#include <machine/autoconf.h>
47
48#include <machine/db_machdep.h>	/* XXX always needed for inst_store() */
49#ifdef DDB
50#ifdef TRAPDEBUG
51#include <ddb/db_output.h>
52#endif
53#endif
54
55const char *trap_type[] = {
56	"invalid",
57	"HPMC",
58	"power failure",
59	"recovery counter",
60	"external interrupt",
61	"LPMC",
62	"ITLB miss fault",
63	"instruction protection",
64	"Illegal instruction",
65	"break instruction",
66	"privileged operation",
67	"privileged register",
68	"overflow",
69	"conditional",
70	"assist exception",
71	"DTLB miss",
72	"ITLB non-access miss",
73	"DTLB non-access miss",
74	"data protection/rights/alignment",
75	"data break",
76	"TLB dirty",
77	"page reference",
78	"assist emulation",
79	"higher-priv transfer",
80	"lower-priv transfer",
81	"taken branch",
82	"data access rights",
83	"data protection",
84	"unaligned data ref",
85};
86int trap_types = sizeof(trap_type)/sizeof(trap_type[0]);
87
88int want_resched, astpending;
89
90#define	frame_regmap(tf,r)	(((u_int *)(tf))[hppa_regmap[(r)]])
91u_char hppa_regmap[32] = {
92	offsetof(struct trapframe, tf_pad[0]) / 4,	/* r0 XXX */
93	offsetof(struct trapframe, tf_r1) / 4,
94	offsetof(struct trapframe, tf_rp) / 4,
95	offsetof(struct trapframe, tf_r3) / 4,
96	offsetof(struct trapframe, tf_r4) / 4,
97	offsetof(struct trapframe, tf_r5) / 4,
98	offsetof(struct trapframe, tf_r6) / 4,
99	offsetof(struct trapframe, tf_r7) / 4,
100	offsetof(struct trapframe, tf_r8) / 4,
101	offsetof(struct trapframe, tf_r9) / 4,
102	offsetof(struct trapframe, tf_r10) / 4,
103	offsetof(struct trapframe, tf_r11) / 4,
104	offsetof(struct trapframe, tf_r12) / 4,
105	offsetof(struct trapframe, tf_r13) / 4,
106	offsetof(struct trapframe, tf_r14) / 4,
107	offsetof(struct trapframe, tf_r15) / 4,
108	offsetof(struct trapframe, tf_r16) / 4,
109	offsetof(struct trapframe, tf_r17) / 4,
110	offsetof(struct trapframe, tf_r18) / 4,
111	offsetof(struct trapframe, tf_t4) / 4,
112	offsetof(struct trapframe, tf_t3) / 4,
113	offsetof(struct trapframe, tf_t2) / 4,
114	offsetof(struct trapframe, tf_t1) / 4,
115	offsetof(struct trapframe, tf_arg3) / 4,
116	offsetof(struct trapframe, tf_arg2) / 4,
117	offsetof(struct trapframe, tf_arg1) / 4,
118	offsetof(struct trapframe, tf_arg0) / 4,
119	offsetof(struct trapframe, tf_dp) / 4,
120	offsetof(struct trapframe, tf_ret0) / 4,
121	offsetof(struct trapframe, tf_ret1) / 4,
122	offsetof(struct trapframe, tf_sp) / 4,
123	offsetof(struct trapframe, tf_r31) / 4,
124};
125
126void
127userret(struct proc *p, register_t pc, u_quad_t oticks)
128{
129	int sig;
130
131	/* take pending signals */
132	while ((sig = CURSIG(p)) != 0)
133		postsig(sig);
134
135	p->p_priority = p->p_usrpri;
136	if (astpending) {
137		astpending = 0;
138		if (p->p_flag & P_OWEUPC) {
139			p->p_flag &= ~P_OWEUPC;
140			ADDUPROF(p);
141		}
142	}
143	if (want_resched) {
144		/*
145		 * We're being preempted.
146		 */
147		preempt(NULL);
148		while ((sig = CURSIG(p)) != 0)
149			postsig(sig);
150	}
151
152	/*
153	 * If profiling, charge recent system time to the trapped pc.
154	 */
155	if (p->p_flag & P_PROFIL) {
156		extern int psratio;
157
158		addupc_task(p, pc, (int)(p->p_sticks - oticks) * psratio);
159	}
160
161	curpriority = p->p_priority;
162}
163
164void
165trap(type, frame)
166	int type;
167	struct trapframe *frame;
168{
169	struct proc *p = curproc;
170	vaddr_t va;
171	struct vm_map *map;
172	struct vmspace *vm;
173	register vm_prot_t vftype;
174	register pa_space_t space;
175	union sigval sv;
176	u_int opcode;
177	int ret, trapnum;
178	const char *tts;
179	vm_fault_t fault = VM_FAULT_INVALID;
180#ifdef DIAGNOSTIC
181	int oldcpl = cpl;
182#endif
183
184	trapnum = type & ~T_USER;
185	opcode = frame->tf_iir;
186	if (trapnum == T_ITLBMISS ||
187	    trapnum == T_EXCEPTION || trapnum == T_EMULATION) {
188		va = frame->tf_iioq_head;
189		space = frame->tf_iisq_head;
190		vftype = UVM_PROT_EXEC;
191	} else {
192		va = frame->tf_ior;
193		space = frame->tf_isr;
194		/* what is the vftype for the T_ITLBMISSNA ??? XXX */
195		if (va == frame->tf_iioq_head)
196			vftype = UVM_PROT_EXEC;
197		else if (inst_store(opcode))
198			vftype = UVM_PROT_WRITE;
199		else
200			vftype = UVM_PROT_READ;
201	}
202
203	if (frame->tf_flags & TFF_LAST)
204		p->p_md.md_regs = frame;
205
206	if (trapnum > trap_types)
207		tts = "reserved";
208	else
209		tts = trap_type[trapnum];
210
211#ifdef TRAPDEBUG
212	if (trapnum != T_INTERRUPT && trapnum != T_IBREAK)
213		db_printf("trap: %x, %s for %x:%x at %x:%x, fl=%x, fp=%p\n",
214		    type, tts, space, va, frame->tf_iisq_head,
215		    frame->tf_iioq_head, frame->tf_flags, frame);
216	else if (trapnum  == T_IBREAK)
217		db_printf("trap: break instruction %x:%x at %x:%x, fp=%p\n",
218		    break5(opcode), break13(opcode),
219		    frame->tf_iisq_head, frame->tf_iioq_head, frame);
220
221	{
222		extern int etext;
223		if (frame < (struct trapframe *)&etext) {
224			printf("trap: bogus frame ptr %p\n", frame);
225			goto dead_end;
226		}
227	}
228#endif
229	if (trapnum != T_INTERRUPT) {
230		uvmexp.traps++;
231		mtctl(frame->tf_eiem, CR_EIEM);
232	} else
233		uvmexp.intrs++;
234
235	switch (type) {
236	case T_NONEXIST:
237	case T_NONEXIST | T_USER:
238		/* we've got screwed up by the central scrutinizer */
239		printf("trap: elvis has just left the building!\n");
240		goto dead_end;
241
242	case T_RECOVERY:
243	case T_RECOVERY | T_USER:
244		/* XXX will implement later */
245		printf("trap: handicapped");
246		goto dead_end;
247
248#ifdef DIAGNOSTIC
249	case T_EXCEPTION:
250		panic("FPU/SFU emulation botch");
251
252		/* these just can't happen ever */
253	case T_PRIV_OP:
254	case T_PRIV_REG:
255		/* these just can't make it to the trap() ever */
256	case T_HPMC:
257	case T_HPMC | T_USER:
258#endif
259	case T_IBREAK:
260	case T_DATALIGN:
261	case T_DBREAK:
262	dead_end:
263#ifdef DDB
264		if (kdb_trap (type, va, frame)) {
265			if (type == T_IBREAK) {
266				/* skip break instruction */
267				frame->tf_iioq_head = frame->tf_iioq_tail;
268				frame->tf_iioq_tail += 4;
269			}
270			return;
271		}
272#else
273		if (type == T_DATALIGN)
274			panic ("trap: %s at 0x%x", tts, va);
275		else
276			panic ("trap: no debugger for \"%s\" (%d)", tts, type);
277#endif
278		break;
279
280	case T_IBREAK | T_USER:
281	case T_DBREAK | T_USER:
282		/* pass to user debugger */
283		trapsignal(p, SIGTRAP, type &~ T_USER, TRAP_BRKPT, sv);
284		break;
285
286	case T_EXCEPTION | T_USER: {
287		u_int64_t *fpp = (u_int64_t *)frame->tf_cr30;
288		u_int32_t *pex;
289		int i, flt;
290
291		pex = (u_int32_t *)&fpp[0];
292		for (i = 0, pex++; i < 7 && !*pex; i++, pex++);
293		flt = 0;
294		if (i < 7) {
295			u_int32_t stat = HPPA_FPU_OP(*pex);
296			if (stat & HPPA_FPU_UNMPL)
297				flt = FPE_FLTINV;
298			else if (stat & (HPPA_FPU_V << 1))
299				flt = FPE_FLTINV;
300			else if (stat & (HPPA_FPU_Z << 1))
301				flt = FPE_FLTDIV;
302			else if (stat & (HPPA_FPU_I << 1))
303				flt = FPE_FLTRES;
304			else if (stat & (HPPA_FPU_O << 1))
305				flt = FPE_FLTOVF;
306			else if (stat & (HPPA_FPU_U << 1))
307				flt = FPE_FLTUND;
308			/* still left: under/over-flow w/ inexact */
309			*pex = 0;
310		}
311		/* reset the trap flag, as if there was none */
312		fpp[0] &= ~(((u_int64_t)HPPA_FPU_T) << 32);
313		/* flush out, since load is done from phys, only 4 regs */
314		fdcache(HPPA_SID_KERNEL, (vaddr_t)fpp, 8 * 4);
315
316		sv.sival_int = va;
317		trapsignal(p, SIGFPE, type &~ T_USER, flt, sv);
318		}
319		break;
320
321	case T_EMULATION:
322		panic("trap: emulation trap in the kernel");
323		break;
324
325	case T_EMULATION | T_USER:
326		sv.sival_int = va;
327		trapsignal(p, SIGILL, type &~ T_USER, ILL_COPROC, sv);
328		break;
329
330	case T_OVERFLOW | T_USER:
331		sv.sival_int = va;
332		trapsignal(p, SIGFPE, type &~ T_USER, FPE_INTOVF, sv);
333		break;
334
335	case T_CONDITION | T_USER:
336		sv.sival_int = va;
337		trapsignal(p, SIGFPE, type &~ T_USER, FPE_INTDIV, sv);
338		break;
339
340	case T_PRIV_OP | T_USER:
341		sv.sival_int = va;
342		trapsignal(p, SIGILL, type &~ T_USER, ILL_PRVOPC, sv);
343		break;
344
345	case T_PRIV_REG | T_USER:
346		sv.sival_int = va;
347		trapsignal(p, SIGILL, type &~ T_USER, ILL_PRVREG, sv);
348		break;
349
350		/* these should never got here */
351	case T_HIGHERPL | T_USER:
352	case T_LOWERPL | T_USER:
353		sv.sival_int = va;
354		trapsignal(p, SIGSEGV, vftype, SEGV_ACCERR, sv);
355		break;
356
357	case T_IPROT | T_USER:
358	case T_DPROT | T_USER:
359		sv.sival_int = va;
360		trapsignal(p, SIGSEGV, vftype, SEGV_ACCERR, sv);
361		break;
362
363	case T_DATACC:
364	case T_DATACC | T_USER:
365		fault = VM_FAULT_PROTECT;
366	case T_ITLBMISS:
367	case T_ITLBMISS | T_USER:
368	case T_DTLBMISS:
369	case T_DTLBMISS | T_USER:
370	case T_ITLBMISSNA:
371	case T_ITLBMISSNA | T_USER:
372	case T_DTLBMISSNA:
373	case T_DTLBMISSNA | T_USER:
374	case T_TLB_DIRTY:
375	case T_TLB_DIRTY | T_USER:
376		/*
377		 * user faults out of user addr space are always a fail,
378		 * this happens on va >= VM_MAXUSER_ADDRESS, where
379		 * space id will be zero and therefore cause
380		 * a misbehave lower in the code.
381		 */
382		if (type & T_USER && va >= VM_MAXUSER_ADDRESS) {
383			sv.sival_int = va;
384			trapsignal(p, SIGSEGV, vftype, SEGV_ACCERR, sv);
385			break;
386		}
387
388		/*
389		 * it could be a kernel map for exec_map faults
390		 */
391		if (space == HPPA_SID_KERNEL)
392			map = kernel_map;
393		else {
394			vm = p->p_vmspace;
395			map = &vm->vm_map;
396		}
397
398		if (type & T_USER && map->pmap->pm_space != space) {
399			sv.sival_int = va;
400			trapsignal(p, SIGSEGV, vftype, SEGV_MAPERR, sv);
401			break;
402		}
403
404		ret = uvm_fault(map, hppa_trunc_page(va), fault, vftype);
405
406		/* dig probe insn */
407		if (ret && trapnum == T_DTLBMISSNA &&
408		    (opcode & 0xfc001f80) == 0x04001180) {
409			frame_regmap(frame, opcode & 0x1f) = 0;
410			frame->tf_ipsw |= PSL_N;
411			break;
412		}
413
414		/*
415		 * If this was a stack access we keep track of the maximum
416		 * accessed stack size.  Also, if uvm_fault gets a protection
417		 * failure it is due to accessing the stack region outside
418		 * the current limit and we need to reflect that as an access
419		 * error.
420		 */
421		if (space != HPPA_SID_KERNEL &&
422		    va < (vaddr_t)vm->vm_minsaddr &&
423		    va >= (vaddr_t)vm->vm_maxsaddr + ctob(vm->vm_ssize)) {
424			if (ret == 0) {
425				vsize_t nss = btoc(va - USRSTACK + NBPG - 1);
426				if (nss > vm->vm_ssize)
427					vm->vm_ssize = nss;
428			} else if (ret == EACCES)
429				ret = EFAULT;
430		}
431
432		if (ret != 0) {
433			if (type & T_USER) {
434				sv.sival_int = va;
435				trapsignal(p, SIGSEGV, vftype,
436				    ret == EACCES? SEGV_ACCERR : SEGV_MAPERR,
437				    sv);
438			} else {
439				if (p && p->p_addr->u_pcb.pcb_onfault) {
440					frame->tf_iioq_tail = 4 +
441					    (frame->tf_iioq_head =
442						p->p_addr->u_pcb.pcb_onfault);
443#ifdef DDB
444					frame->tf_iir = 0;
445#endif
446				} else {
447					panic("trap: "
448					    "uvm_fault(%p, %lx, %d, %d): %d",
449					    map, va, fault, vftype, ret);
450				}
451			}
452		}
453		break;
454
455	case T_DATALIGN | T_USER:
456		sv.sival_int = va;
457		trapsignal(p, SIGBUS, vftype, BUS_ADRALN, sv);
458		break;
459
460	case T_INTERRUPT:
461	case T_INTERRUPT | T_USER:
462		cpu_intr(frame);
463		break;
464
465	case T_CONDITION:
466		panic("trap: divide by zero in the kernel");
467		break;
468
469	case T_ILLEGAL:
470	case T_ILLEGAL | T_USER:
471		/* see if it's a SPOP1,,0 */
472		if ((opcode & 0xfffffe00) == 0x10000200) {
473			frame_regmap(frame, opcode & 0x1f) = 0;
474			frame->tf_ipsw |= PSL_N;
475			break;
476		}
477		if (type & T_USER) {
478			sv.sival_int = va;
479			trapsignal(p, SIGILL, type &~ T_USER, ILL_ILLOPC, sv);
480			break;
481		}
482		/* FALLTHROUGH */
483
484	case T_LOWERPL:
485	case T_DPROT:
486	case T_IPROT:
487	case T_OVERFLOW:
488	case T_HIGHERPL:
489	case T_TAKENBR:
490	case T_POWERFAIL:
491	case T_LPMC:
492	case T_PAGEREF:
493	case T_DATAPID:
494	case T_DATAPID | T_USER:
495		if (0 /* T-chip */) {
496			break;
497		}
498		/* FALLTHROUGH to unimplemented */
499	default:
500#if 0
501if (kdb_trap (type, va, frame))
502	return;
503#endif
504		panic("trap: unimplemented \'%s\' (%d)", tts, trapnum);
505	}
506
507#ifdef DIAGNOSTIC
508	if (cpl != oldcpl)
509		printf("WARNING: SPL (%d) NOT LOWERED ON "
510		    "TRAP (%d) EXIT\n", cpl, trapnum);
511#endif
512
513	if (trapnum != T_INTERRUPT)
514		splx(cpl);	/* process softints */
515
516	/*
517	 * in case we were interrupted from the syscall gate page
518	 * treat this as we were not realy running user code no more
519	 * for weird things start to happen on return to the userland
520	 * and also see a note in locore.S:TLABEL(all)
521	 */
522	if ((type & T_USER) &&
523	    (frame->tf_iioq_head & ~PAGE_MASK) != SYSCALLGATE)
524		userret(p, frame->tf_iioq_head, 0);
525}
526
527void
528child_return(arg)
529	void *arg;
530{
531	struct proc *p = (struct proc *)arg;
532	struct trapframe *tf = p->p_md.md_regs;
533
534	/*
535	 * Set up return value registers as libc:fork() expects
536	 */
537	tf->tf_ret0 = 0;
538	tf->tf_ret1 = 1;	/* ischild */
539	tf->tf_t1 = 0;		/* errno */
540
541	userret(p, tf->tf_iioq_head, 0);
542#ifdef KTRACE
543	if (KTRPOINT(p, KTR_SYSRET))
544		ktrsysret(p, SYS_fork, 0, 0);
545#endif
546}
547
548
549/*
550 * call actual syscall routine
551 */
552void
553syscall(struct trapframe *frame)
554{
555	register struct proc *p = curproc;
556	register const struct sysent *callp;
557	int retq, nsys, code, argsize, argoff, oerror, error;
558	register_t args[8], rval[2];
559#ifdef DIAGNOSTIC
560	int oldcpl = cpl;
561#endif
562
563	uvmexp.syscalls++;
564
565	if (!USERMODE(frame->tf_iioq_head))
566		panic("syscall");
567
568	p->p_md.md_regs = frame;
569	nsys = p->p_emul->e_nsysent;
570	callp = p->p_emul->e_sysent;
571
572	argoff = 4; retq = 0;
573	switch (code = frame->tf_t1) {
574	case SYS_syscall:
575		code = frame->tf_arg0;
576		args[0] = frame->tf_arg1;
577		args[1] = frame->tf_arg2;
578		args[2] = frame->tf_arg3;
579		argoff = 3;
580		break;
581	case SYS___syscall:
582		if (callp != sysent)
583			break;
584		/*
585		 * this works, because quads get magically swapped
586		 * due to the args being laid backwards on the stack
587		 * and then copied in words
588		 */
589		code = frame->tf_arg0;
590		args[0] = frame->tf_arg2;
591		args[1] = frame->tf_arg3;
592		argoff = 2;
593		retq = 1;
594		break;
595	default:
596		args[0] = frame->tf_arg0;
597		args[1] = frame->tf_arg1;
598		args[2] = frame->tf_arg2;
599		args[3] = frame->tf_arg3;
600		break;
601	}
602
603	if (code < 0 || code >= nsys)
604		callp += p->p_emul->e_nosys;	/* bad syscall # */
605	else
606		callp += code;
607
608	oerror = error = 0;
609	if ((argsize = callp->sy_argsize)) {
610		int i;
611
612		for (i = 0, argsize -= argoff * 4;
613		    argsize > 0; i++, argsize -= 4) {
614			error = copyin((void *)(frame->tf_sp +
615			    HPPA_FRAME_ARG(i + 4)), args + i + argoff, 4);
616
617			if (error)
618				break;
619		}
620
621		/*
622		 * coming from syscall() or __syscall we must be
623		 * having one of those w/ a 64 bit arguments,
624		 * which needs a word swap due to the order
625		 * of the arguments on the stack.
626		 * this assumes that none of 'em are called
627		 * by their normal syscall number, maybe a regress
628		 * test should be used, to watch the behaviour.
629		 */
630		if (!error && argoff < 4) {
631			int t;
632
633			i = 0;
634			switch (code) {
635			case SYS_lseek:		retq = 0;
636			case SYS_truncate:
637			case SYS_ftruncate:	i = 2;	break;
638			case SYS_preadv:
639			case SYS_pwritev:
640			case SYS_pread:
641			case SYS_pwrite:	i = 4;	break;
642			case SYS_mmap:		i = 6;	break;
643			}
644
645			if (i) {
646				t = args[i];
647				args[i] = args[i + 1];
648				args[i + 1] = t;
649			}
650		}
651	}
652
653#ifdef SYSCALL_DEBUG
654	scdebug_call(p, code, args);
655#endif
656#ifdef KTRACE
657	if (KTRPOINT(p, KTR_SYSCALL))
658		ktrsyscall(p, code, callp->sy_argsize, args);
659#endif
660	if (error)
661		goto bad;
662
663	rval[0] = 0;
664	rval[1] = frame->tf_ret1;
665#if NSYSTRACE > 0
666	if (ISSET(p->p_flag, P_SYSTRACE))
667		oerror = error = systrace_redirect(code, p, args, rval);
668	else
669#endif
670		oerror = error = (*callp->sy_call)(p, args, rval);
671	p = curproc;
672	frame = p->p_md.md_regs;
673	switch (error) {
674	case 0:
675		frame->tf_ret0 = rval[0];
676		frame->tf_ret1 = rval[!retq];
677		frame->tf_t1 = 0;
678		break;
679	case ERESTART:
680		frame->tf_iioq_head -= 12;
681		frame->tf_iioq_tail -= 12;
682	case EJUSTRETURN:
683		break;
684	default:
685	bad:
686		if (p->p_emul->e_errno)
687			error = p->p_emul->e_errno[error];
688		frame->tf_t1 = error;
689		break;
690	}
691#ifdef SYSCALL_DEBUG
692	scdebug_ret(p, code, oerror, rval);
693#endif
694	userret(p, frame->tf_iioq_head, 0);
695#ifdef KTRACE
696	if (KTRPOINT(p, KTR_SYSRET))
697		ktrsysret(p, code, oerror, rval[0]);
698#endif
699#ifdef DIAGNOSTIC
700	if (cpl != oldcpl) {
701		printf("WARNING: SPL (0x%x) NOT LOWERED ON "
702		    "syscall(0x%x, 0x%x, 0x%x, 0x%x...) EXIT, PID %d\n",
703		    cpl, code, args[0], args[1], args[2], p->p_pid);
704		cpl = oldcpl;
705	}
706#endif
707	splx(cpl);	/* process softints */
708}
709