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