trap.c revision 1.90
1/*	$OpenBSD: trap.c,v 1.90 2005/09/15 21:14:27 miod 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
55#ifdef PTRACE
56#include <miscfs/procfs/procfs.h>
57void ss_clear_breakpoints(struct proc *p);
58#endif
59
60/* single-step breakpoint */
61#define SSBREAKPOINT	(HPPA_BREAK_KERNEL | (HPPA_BREAK_SS << 13))
62
63const char *trap_type[] = {
64	"invalid",
65	"HPMC",
66	"power failure",
67	"recovery counter",
68	"external interrupt",
69	"LPMC",
70	"ITLB miss fault",
71	"instruction protection",
72	"Illegal instruction",
73	"break instruction",
74	"privileged operation",
75	"privileged register",
76	"overflow",
77	"conditional",
78	"assist exception",
79	"DTLB miss",
80	"ITLB non-access miss",
81	"DTLB non-access miss",
82	"data protection/rights/alignment",
83	"data break",
84	"TLB dirty",
85	"page reference",
86	"assist emulation",
87	"higher-priv transfer",
88	"lower-priv transfer",
89	"taken branch",
90	"data access rights",
91	"data protection",
92	"unaligned data ref",
93};
94int trap_types = sizeof(trap_type)/sizeof(trap_type[0]);
95
96int want_resched, astpending;
97
98#define	frame_regmap(tf,r)	(((u_int *)(tf))[hppa_regmap[(r)]])
99u_char hppa_regmap[32] = {
100	offsetof(struct trapframe, tf_pad[0]) / 4,	/* r0 XXX */
101	offsetof(struct trapframe, tf_r1) / 4,
102	offsetof(struct trapframe, tf_rp) / 4,
103	offsetof(struct trapframe, tf_r3) / 4,
104	offsetof(struct trapframe, tf_r4) / 4,
105	offsetof(struct trapframe, tf_r5) / 4,
106	offsetof(struct trapframe, tf_r6) / 4,
107	offsetof(struct trapframe, tf_r7) / 4,
108	offsetof(struct trapframe, tf_r8) / 4,
109	offsetof(struct trapframe, tf_r9) / 4,
110	offsetof(struct trapframe, tf_r10) / 4,
111	offsetof(struct trapframe, tf_r11) / 4,
112	offsetof(struct trapframe, tf_r12) / 4,
113	offsetof(struct trapframe, tf_r13) / 4,
114	offsetof(struct trapframe, tf_r14) / 4,
115	offsetof(struct trapframe, tf_r15) / 4,
116	offsetof(struct trapframe, tf_r16) / 4,
117	offsetof(struct trapframe, tf_r17) / 4,
118	offsetof(struct trapframe, tf_r18) / 4,
119	offsetof(struct trapframe, tf_t4) / 4,
120	offsetof(struct trapframe, tf_t3) / 4,
121	offsetof(struct trapframe, tf_t2) / 4,
122	offsetof(struct trapframe, tf_t1) / 4,
123	offsetof(struct trapframe, tf_arg3) / 4,
124	offsetof(struct trapframe, tf_arg2) / 4,
125	offsetof(struct trapframe, tf_arg1) / 4,
126	offsetof(struct trapframe, tf_arg0) / 4,
127	offsetof(struct trapframe, tf_dp) / 4,
128	offsetof(struct trapframe, tf_ret0) / 4,
129	offsetof(struct trapframe, tf_ret1) / 4,
130	offsetof(struct trapframe, tf_sp) / 4,
131	offsetof(struct trapframe, tf_r31) / 4,
132};
133
134void
135userret(struct proc *p, register_t pc, u_quad_t oticks)
136{
137	int sig;
138
139	/* take pending signals */
140	while ((sig = CURSIG(p)) != 0)
141		postsig(sig);
142
143	p->p_priority = p->p_usrpri;
144	if (astpending) {
145		astpending = 0;
146		if (p->p_flag & P_OWEUPC) {
147			p->p_flag &= ~P_OWEUPC;
148			ADDUPROF(p);
149		}
150	}
151	if (want_resched) {
152		/*
153		 * We're being preempted.
154		 */
155		preempt(NULL);
156		while ((sig = CURSIG(p)) != 0)
157			postsig(sig);
158	}
159
160	/*
161	 * If profiling, charge recent system time to the trapped pc.
162	 */
163	if (p->p_flag & P_PROFIL) {
164		extern int psratio;
165
166		addupc_task(p, pc, (int)(p->p_sticks - oticks) * psratio);
167	}
168
169	curpriority = p->p_priority;
170}
171
172void
173trap(type, frame)
174	int type;
175	struct trapframe *frame;
176{
177	struct proc *p = curproc;
178	vaddr_t va;
179	struct vm_map *map;
180	struct vmspace *vm;
181	register vm_prot_t vftype;
182	register pa_space_t space;
183	union sigval sv;
184	u_int opcode;
185	int ret, trapnum;
186	const char *tts;
187	vm_fault_t fault = VM_FAULT_INVALID;
188#ifdef DIAGNOSTIC
189	int oldcpl = cpl;
190#endif
191
192	trapnum = type & ~T_USER;
193	opcode = frame->tf_iir;
194	if (trapnum <= T_EXCEPTION || trapnum == T_HIGHERPL ||
195	    trapnum == T_LOWERPL || trapnum == T_TAKENBR ||
196	    trapnum == T_IDEBUG || trapnum == T_PERFMON) {
197		va = frame->tf_iioq_head;
198		space = frame->tf_iisq_head;
199		vftype = UVM_PROT_EXEC;
200	} else {
201		va = frame->tf_ior;
202		space = frame->tf_isr;
203		if (va == frame->tf_iioq_head)
204			vftype = UVM_PROT_EXEC;
205		else if (inst_store(opcode))
206			vftype = UVM_PROT_WRITE;
207		else
208			vftype = UVM_PROT_READ;
209	}
210
211	if (frame->tf_flags & TFF_LAST)
212		p->p_md.md_regs = frame;
213
214	if (trapnum > trap_types)
215		tts = "reserved";
216	else
217		tts = trap_type[trapnum];
218
219#ifdef TRAPDEBUG
220	if (trapnum != T_INTERRUPT && trapnum != T_IBREAK)
221		db_printf("trap: %x, %s for %x:%x at %x:%x, fl=%x, fp=%p\n",
222		    type, tts, space, va, frame->tf_iisq_head,
223		    frame->tf_iioq_head, frame->tf_flags, frame);
224	else if (trapnum  == T_IBREAK)
225		db_printf("trap: break instruction %x:%x at %x:%x, fp=%p\n",
226		    break5(opcode), break13(opcode),
227		    frame->tf_iisq_head, frame->tf_iioq_head, frame);
228
229	{
230		extern int etext;
231		if (frame < (struct trapframe *)&etext) {
232			printf("trap: bogus frame ptr %p\n", frame);
233			goto dead_end;
234		}
235	}
236#endif
237	if (trapnum != T_INTERRUPT) {
238		uvmexp.traps++;
239		mtctl(frame->tf_eiem, CR_EIEM);
240	}
241
242	switch (type) {
243	case T_NONEXIST:
244	case T_NONEXIST | T_USER:
245		/* we've got screwed up by the central scrutinizer */
246		printf("trap: elvis has just left the building!\n");
247		goto dead_end;
248
249	case T_RECOVERY:
250	case T_RECOVERY | T_USER:
251		/* XXX will implement later */
252		printf("trap: handicapped");
253		goto dead_end;
254
255#ifdef DIAGNOSTIC
256	case T_EXCEPTION:
257		panic("FPU/SFU emulation botch");
258
259		/* these just can't happen ever */
260	case T_PRIV_OP:
261	case T_PRIV_REG:
262		/* these just can't make it to the trap() ever */
263	case T_HPMC:
264	case T_HPMC | T_USER:
265#endif
266	case T_IBREAK:
267	case T_DATALIGN:
268	case T_DBREAK:
269	dead_end:
270#ifdef DDB
271		if (kdb_trap (type, va, frame)) {
272			if (type == T_IBREAK) {
273				/* skip break instruction */
274				frame->tf_iioq_head = frame->tf_iioq_tail;
275				frame->tf_iioq_tail += 4;
276			}
277			return;
278		}
279#else
280		if (type == T_DATALIGN)
281			panic ("trap: %s at 0x%x", tts, va);
282		else
283			panic ("trap: no debugger for \"%s\" (%d)", tts, type);
284#endif
285		break;
286
287	case T_IBREAK | T_USER:
288	case T_DBREAK | T_USER: {
289		int code = TRAP_BRKPT;
290#ifdef PTRACE
291		ss_clear_breakpoints(p);
292		if (opcode == SSBREAKPOINT)
293			code = TRAP_TRACE;
294#endif
295		/* pass to user debugger */
296		trapsignal(p, SIGTRAP, type &~ T_USER, code, sv);
297		}
298		break;
299
300#ifdef PTRACE
301	case T_TAKENBR | T_USER:
302		ss_clear_breakpoints(p);
303
304		/* pass to user debugger */
305		trapsignal(p, SIGTRAP, type &~ T_USER, TRAP_TRACE, sv);
306		break;
307#endif
308
309	case T_EXCEPTION | T_USER: {
310		u_int64_t *fpp = (u_int64_t *)frame->tf_cr30;
311		u_int32_t *pex;
312		int i, flt;
313
314		pex = (u_int32_t *)&fpp[0];
315		for (i = 0, pex++; i < 7 && !*pex; i++, pex++);
316		flt = 0;
317		if (i < 7) {
318			u_int32_t stat = HPPA_FPU_OP(*pex);
319			if (stat & HPPA_FPU_UNMPL)
320				flt = FPE_FLTINV;
321			else if (stat & (HPPA_FPU_V << 1))
322				flt = FPE_FLTINV;
323			else if (stat & (HPPA_FPU_Z << 1))
324				flt = FPE_FLTDIV;
325			else if (stat & (HPPA_FPU_I << 1))
326				flt = FPE_FLTRES;
327			else if (stat & (HPPA_FPU_O << 1))
328				flt = FPE_FLTOVF;
329			else if (stat & (HPPA_FPU_U << 1))
330				flt = FPE_FLTUND;
331			/* still left: under/over-flow w/ inexact */
332
333			/* cleanup exceptions (XXX deliver all ?) */
334			while (i++ < 7)
335				*pex++ = 0;
336		}
337		/* reset the trap flag, as if there was none */
338		fpp[0] &= ~(((u_int64_t)HPPA_FPU_T) << 32);
339		/* flush out, since load is done from phys, only 4 regs */
340		fdcache(HPPA_SID_KERNEL, (vaddr_t)fpp, 8 * 4);
341
342		sv.sival_int = va;
343		trapsignal(p, SIGFPE, type &~ T_USER, flt, sv);
344		}
345		break;
346
347	case T_EMULATION:
348		panic("trap: emulation trap in the kernel");
349		break;
350
351	case T_EMULATION | T_USER:
352		sv.sival_int = va;
353		trapsignal(p, SIGILL, type &~ T_USER, ILL_COPROC, sv);
354		break;
355
356	case T_OVERFLOW | T_USER:
357		sv.sival_int = va;
358		trapsignal(p, SIGFPE, type &~ T_USER, FPE_INTOVF, sv);
359		break;
360
361	case T_CONDITION | T_USER:
362		sv.sival_int = va;
363		trapsignal(p, SIGFPE, type &~ T_USER, FPE_INTDIV, sv);
364		break;
365
366	case T_PRIV_OP | T_USER:
367		sv.sival_int = va;
368		trapsignal(p, SIGILL, type &~ T_USER, ILL_PRVOPC, sv);
369		break;
370
371	case T_PRIV_REG | T_USER:
372		sv.sival_int = va;
373		trapsignal(p, SIGILL, type &~ T_USER, ILL_PRVREG, sv);
374		break;
375
376		/* these should never got here */
377	case T_HIGHERPL | T_USER:
378	case T_LOWERPL | T_USER:
379		sv.sival_int = va;
380		trapsignal(p, SIGSEGV, vftype, SEGV_ACCERR, sv);
381		break;
382
383	case T_IPROT | T_USER:
384	case T_DPROT | T_USER:
385		sv.sival_int = va;
386		trapsignal(p, SIGSEGV, vftype, SEGV_ACCERR, sv);
387		break;
388
389	case T_ITLBMISSNA:
390	case T_ITLBMISSNA | T_USER:
391	case T_DTLBMISSNA:
392	case T_DTLBMISSNA | T_USER:
393		if (space == HPPA_SID_KERNEL)
394			map = kernel_map;
395		else {
396			vm = p->p_vmspace;
397			map = &vm->vm_map;
398		}
399
400		if ((opcode & 0xfc003fc0) == 0x04001340) {
401			/* lpa failure case */
402			frame_regmap(frame, opcode & 0x1f) = 0;
403			frame->tf_ipsw |= PSL_N;
404		} else if ((opcode & 0xfc001f80) == 0x04001180) {
405			int pl;
406
407			/* dig probe[rw]i? insns */
408			if (opcode & 0x2000)
409				pl = (opcode >> 16) & 3;
410			else
411				pl = frame_regmap(frame,
412				    (opcode >> 16) & 0x1f) & 3;
413
414			if ((type & T_USER && space == HPPA_SID_KERNEL) ||
415			    (frame->tf_iioq_head & 3) != pl ||
416			    (type & T_USER && va >= VM_MAXUSER_ADDRESS) ||
417			    uvm_fault(map, hppa_trunc_page(va), fault,
418			     opcode & 0x40? UVM_PROT_WRITE : UVM_PROT_READ)) {
419				frame_regmap(frame, opcode & 0x1f) = 0;
420				frame->tf_ipsw |= PSL_N;
421			}
422		} else if (type & T_USER) {
423			sv.sival_int = va;
424			trapsignal(p, SIGILL, type & ~T_USER, ILL_ILLTRP, sv);
425		} else
426			panic("trap: %s @ 0x%x:0x%x for 0x%x:0x%x irr 0x%08x",
427			    tts, frame->tf_iisq_head, frame->tf_iioq_head,
428			    space, va, opcode);
429		break;
430
431	case T_TLB_DIRTY:
432	case T_TLB_DIRTY | T_USER:
433	case T_DATACC:
434	case T_DATACC | T_USER:
435		fault = VM_FAULT_PROTECT;
436	case T_ITLBMISS:
437	case T_ITLBMISS | T_USER:
438	case T_DTLBMISS:
439	case T_DTLBMISS | T_USER:
440		/*
441		 * it could be a kernel map for exec_map faults
442		 */
443		if (space == HPPA_SID_KERNEL)
444			map = kernel_map;
445		else {
446			vm = p->p_vmspace;
447			map = &vm->vm_map;
448		}
449
450		/*
451		 * user faults out of user addr space are always a fail,
452		 * this happens on va >= VM_MAXUSER_ADDRESS, where
453		 * space id will be zero and therefore cause
454		 * a misbehave lower in the code.
455		 *
456		 * also check that faulted space id matches the curproc.
457		 */
458		if ((type & T_USER && va >= VM_MAXUSER_ADDRESS) ||
459		   (type & T_USER && map->pmap->pm_space != space)) {
460			sv.sival_int = va;
461			trapsignal(p, SIGSEGV, vftype, SEGV_MAPERR, sv);
462			break;
463		}
464
465		ret = uvm_fault(map, hppa_trunc_page(va), fault, vftype);
466
467		/*
468		 * If this was a stack access we keep track of the maximum
469		 * accessed stack size.  Also, if uvm_fault gets a protection
470		 * failure it is due to accessing the stack region outside
471		 * the current limit and we need to reflect that as an access
472		 * error.
473		 */
474		if (space != HPPA_SID_KERNEL &&
475		    va < (vaddr_t)vm->vm_minsaddr) {
476			if (ret == 0)
477				uvm_grow(p, va);
478			else if (ret == EACCES)
479				ret = EFAULT;
480		}
481
482		if (ret != 0) {
483			if (type & T_USER) {
484				sv.sival_int = va;
485				trapsignal(p, SIGSEGV, vftype,
486				    ret == EACCES? SEGV_ACCERR : SEGV_MAPERR,
487				    sv);
488			} else {
489				if (p && p->p_addr->u_pcb.pcb_onfault) {
490					frame->tf_iioq_tail = 4 +
491					    (frame->tf_iioq_head =
492						p->p_addr->u_pcb.pcb_onfault);
493#ifdef DDB
494					frame->tf_iir = 0;
495#endif
496				} else {
497					panic("trap: "
498					    "uvm_fault(%p, %lx, %d, %d): %d",
499					    map, va, fault, vftype, ret);
500				}
501			}
502		}
503		break;
504
505	case T_DATALIGN | T_USER:
506		sv.sival_int = va;
507		trapsignal(p, SIGBUS, vftype, BUS_ADRALN, sv);
508		break;
509
510	case T_INTERRUPT:
511	case T_INTERRUPT | T_USER:
512		cpu_intr(frame);
513		break;
514
515	case T_CONDITION:
516		panic("trap: divide by zero in the kernel");
517		break;
518
519	case T_ILLEGAL:
520	case T_ILLEGAL | T_USER:
521		/* see if it's a SPOP1,,0 */
522		if ((opcode & 0xfffffe00) == 0x10000200) {
523			frame_regmap(frame, opcode & 0x1f) = 0;
524			frame->tf_ipsw |= PSL_N;
525			break;
526		}
527		if (type & T_USER) {
528			sv.sival_int = va;
529			trapsignal(p, SIGILL, type &~ T_USER, ILL_ILLOPC, sv);
530			break;
531		}
532		/* FALLTHROUGH */
533
534	case T_LOWERPL:
535	case T_DPROT:
536	case T_IPROT:
537	case T_OVERFLOW:
538	case T_HIGHERPL:
539	case T_TAKENBR:
540	case T_POWERFAIL:
541	case T_LPMC:
542	case T_PAGEREF:
543	case T_DATAPID:
544	case T_DATAPID | T_USER:
545		if (0 /* T-chip */) {
546			break;
547		}
548		/* FALLTHROUGH to unimplemented */
549	default:
550#if 0
551if (kdb_trap (type, va, frame))
552	return;
553#endif
554		panic("trap: unimplemented \'%s\' (%d)", tts, trapnum);
555	}
556
557#ifdef DIAGNOSTIC
558	if (cpl != oldcpl)
559		printf("WARNING: SPL (%d) NOT LOWERED ON "
560		    "TRAP (%d) EXIT\n", cpl, trapnum);
561#endif
562
563	if (trapnum != T_INTERRUPT)
564		splx(cpl);	/* process softints */
565
566	/*
567	 * in case we were interrupted from the syscall gate page
568	 * treat this as we were not realy running user code no more
569	 * for weird things start to happen on return to the userland
570	 * and also see a note in locore.S:TLABEL(all)
571	 */
572	if ((type & T_USER) &&
573	    (frame->tf_iioq_head & ~PAGE_MASK) != SYSCALLGATE)
574		userret(p, frame->tf_iioq_head, 0);
575}
576
577void
578child_return(arg)
579	void *arg;
580{
581	struct proc *p = (struct proc *)arg;
582	struct trapframe *tf = p->p_md.md_regs;
583
584	/*
585	 * Set up return value registers as libc:fork() expects
586	 */
587	tf->tf_ret0 = 0;
588	tf->tf_ret1 = 1;	/* ischild */
589	tf->tf_t1 = 0;		/* errno */
590
591	userret(p, tf->tf_iioq_head, 0);
592#ifdef KTRACE
593	if (KTRPOINT(p, KTR_SYSRET))
594		ktrsysret(p,
595		    (p->p_flag & P_PPWAIT) ? SYS_vfork : SYS_fork, 0, 0);
596#endif
597}
598
599#ifdef PTRACE
600
601#include <sys/ptrace.h>
602
603int
604ss_get_value(struct proc *p, vaddr_t addr, u_int *value)
605{
606	struct uio uio;
607	struct iovec iov;
608
609	iov.iov_base = (caddr_t)value;
610	iov.iov_len = sizeof(u_int);
611	uio.uio_iov = &iov;
612	uio.uio_iovcnt = 1;
613	uio.uio_offset = (off_t)addr;
614	uio.uio_resid = sizeof(u_int);
615	uio.uio_segflg = UIO_SYSSPACE;
616	uio.uio_rw = UIO_READ;
617	uio.uio_procp = curproc;
618	return (procfs_domem(curproc, p, NULL, &uio));
619}
620
621int
622ss_put_value(struct proc *p, vaddr_t addr, u_int value)
623{
624	struct uio uio;
625	struct iovec iov;
626
627	iov.iov_base = (caddr_t)&value;
628	iov.iov_len = sizeof(u_int);
629	uio.uio_iov = &iov;
630	uio.uio_iovcnt = 1;
631	uio.uio_offset = (off_t)addr;
632	uio.uio_resid = sizeof(u_int);
633	uio.uio_segflg = UIO_SYSSPACE;
634	uio.uio_rw = UIO_WRITE;
635	uio.uio_procp = curproc;
636	return (procfs_domem(curproc, p, NULL, &uio));
637}
638
639void
640ss_clear_breakpoints(struct proc *p)
641{
642	/* Restore origional instructions. */
643	if (p->p_md.md_bpva != 0) {
644		ss_put_value(p, p->p_md.md_bpva, p->p_md.md_bpsave[0]);
645		ss_put_value(p, p->p_md.md_bpva + 4, p->p_md.md_bpsave[1]);
646		p->p_md.md_bpva = 0;
647	}
648}
649
650int
651process_sstep(struct proc *p, int sstep)
652{
653	int error;
654
655	ss_clear_breakpoints(p);
656
657	/* Don't touch the syscall gateway page. */
658	if (sstep == 0 ||
659	    (p->p_md.md_regs->tf_iioq_tail & ~PAGE_MASK) == SYSCALLGATE) {
660		p->p_md.md_regs->tf_ipsw &= ~PSL_T;
661		return (0);
662	}
663
664	p->p_md.md_bpva = p->p_md.md_regs->tf_iioq_tail & ~HPPA_PC_PRIV_MASK;
665
666	/*
667	 * Insert two breakpoint instructions; the first one might be
668	 * nullified.  Of course we need to save two instruction
669	 * first.
670	 */
671
672	error = ss_get_value(p, p->p_md.md_bpva, &p->p_md.md_bpsave[0]);
673	if (error)
674		return (error);
675	error = ss_get_value(p, p->p_md.md_bpva + 4, &p->p_md.md_bpsave[1]);
676	if (error)
677		return (error);
678
679	error = ss_put_value(p, p->p_md.md_bpva, SSBREAKPOINT);
680	if (error)
681		return (error);
682	error = ss_put_value(p, p->p_md.md_bpva + 4, SSBREAKPOINT);
683	if (error)
684		return (error);
685
686	p->p_md.md_regs->tf_ipsw |= PSL_T;
687	return (0);
688}
689
690#endif	/* PTRACE */
691
692/*
693 * call actual syscall routine
694 */
695void
696syscall(struct trapframe *frame)
697{
698	register struct proc *p = curproc;
699	register const struct sysent *callp;
700	int retq, nsys, code, argsize, argoff, oerror, error;
701	register_t args[8], rval[2];
702#ifdef DIAGNOSTIC
703	int oldcpl = cpl;
704#endif
705
706	uvmexp.syscalls++;
707
708	if (!USERMODE(frame->tf_iioq_head))
709		panic("syscall");
710
711	p->p_md.md_regs = frame;
712	nsys = p->p_emul->e_nsysent;
713	callp = p->p_emul->e_sysent;
714
715	argoff = 4; retq = 0;
716	switch (code = frame->tf_t1) {
717	case SYS_syscall:
718		code = frame->tf_arg0;
719		args[0] = frame->tf_arg1;
720		args[1] = frame->tf_arg2;
721		args[2] = frame->tf_arg3;
722		argoff = 3;
723		break;
724	case SYS___syscall:
725		if (callp != sysent)
726			break;
727		/*
728		 * this works, because quads get magically swapped
729		 * due to the args being laid backwards on the stack
730		 * and then copied in words
731		 */
732		code = frame->tf_arg0;
733		args[0] = frame->tf_arg2;
734		args[1] = frame->tf_arg3;
735		argoff = 2;
736		retq = 1;
737		break;
738	default:
739		args[0] = frame->tf_arg0;
740		args[1] = frame->tf_arg1;
741		args[2] = frame->tf_arg2;
742		args[3] = frame->tf_arg3;
743		break;
744	}
745
746	if (code < 0 || code >= nsys)
747		callp += p->p_emul->e_nosys;	/* bad syscall # */
748	else
749		callp += code;
750
751	oerror = error = 0;
752	if ((argsize = callp->sy_argsize)) {
753		int i;
754
755		for (i = 0, argsize -= argoff * 4;
756		    argsize > 0; i++, argsize -= 4) {
757			error = copyin((void *)(frame->tf_sp +
758			    HPPA_FRAME_ARG(i + 4)), args + i + argoff, 4);
759
760			if (error)
761				break;
762		}
763
764		/*
765		 * coming from syscall() or __syscall we must be
766		 * having one of those w/ a 64 bit arguments,
767		 * which needs a word swap due to the order
768		 * of the arguments on the stack.
769		 * this assumes that none of 'em are called
770		 * by their normal syscall number, maybe a regress
771		 * test should be used, to watch the behaviour.
772		 */
773		if (!error && argoff < 4) {
774			int t;
775
776			i = 0;
777			switch (code) {
778			case SYS_lseek:		retq = 0;
779			case SYS_truncate:
780			case SYS_ftruncate:	i = 2;	break;
781			case SYS_preadv:
782			case SYS_pwritev:
783			case SYS_pread:
784			case SYS_pwrite:	i = 4;	break;
785			case SYS_mquery:
786			case SYS_mmap:		i = 6;	break;
787			}
788
789			if (i) {
790				t = args[i];
791				args[i] = args[i + 1];
792				args[i + 1] = t;
793			}
794		}
795	}
796
797#ifdef SYSCALL_DEBUG
798	scdebug_call(p, code, args);
799#endif
800#ifdef KTRACE
801	if (KTRPOINT(p, KTR_SYSCALL))
802		ktrsyscall(p, code, callp->sy_argsize, args);
803#endif
804	if (error)
805		goto bad;
806
807	rval[0] = 0;
808	rval[1] = frame->tf_ret1;
809#if NSYSTRACE > 0
810	if (ISSET(p->p_flag, P_SYSTRACE))
811		oerror = error = systrace_redirect(code, p, args, rval);
812	else
813#endif
814		oerror = error = (*callp->sy_call)(p, args, rval);
815	switch (error) {
816	case 0:
817		frame->tf_ret0 = rval[0];
818		frame->tf_ret1 = rval[!retq];
819		frame->tf_t1 = 0;
820		break;
821	case ERESTART:
822		frame->tf_iioq_head -= 12;
823		frame->tf_iioq_tail -= 12;
824	case EJUSTRETURN:
825		break;
826	default:
827	bad:
828		if (p->p_emul->e_errno)
829			error = p->p_emul->e_errno[error];
830		frame->tf_t1 = error;
831		frame->tf_ret0 = error;
832		frame->tf_ret1 = 0;
833		break;
834	}
835#ifdef SYSCALL_DEBUG
836	scdebug_ret(p, code, oerror, rval);
837#endif
838	userret(p, frame->tf_iioq_head, 0);
839#ifdef KTRACE
840	if (KTRPOINT(p, KTR_SYSRET))
841		ktrsysret(p, code, oerror, rval[0]);
842#endif
843#ifdef DIAGNOSTIC
844	if (cpl != oldcpl) {
845		printf("WARNING: SPL (0x%x) NOT LOWERED ON "
846		    "syscall(0x%x, 0x%x, 0x%x, 0x%x...) EXIT, PID %d\n",
847		    cpl, code, args[0], args[1], args[2], p->p_pid);
848		cpl = oldcpl;
849	}
850#endif
851	splx(cpl);	/* process softints */
852}
853