trap.c revision 1.106
1/*	$OpenBSD: trap.c,v 1.106 2010/03/30 14:57:02 kettenis 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
55int	pcxs_unaligned(u_int opcode, vaddr_t va);
56#ifdef PTRACE
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
96#define	frame_regmap(tf,r)	(((u_int *)(tf))[hppa_regmap[(r)]])
97u_char hppa_regmap[32] = {
98	offsetof(struct trapframe, tf_pad[0]) / 4,	/* r0 XXX */
99	offsetof(struct trapframe, tf_r1) / 4,
100	offsetof(struct trapframe, tf_rp) / 4,
101	offsetof(struct trapframe, tf_r3) / 4,
102	offsetof(struct trapframe, tf_r4) / 4,
103	offsetof(struct trapframe, tf_r5) / 4,
104	offsetof(struct trapframe, tf_r6) / 4,
105	offsetof(struct trapframe, tf_r7) / 4,
106	offsetof(struct trapframe, tf_r8) / 4,
107	offsetof(struct trapframe, tf_r9) / 4,
108	offsetof(struct trapframe, tf_r10) / 4,
109	offsetof(struct trapframe, tf_r11) / 4,
110	offsetof(struct trapframe, tf_r12) / 4,
111	offsetof(struct trapframe, tf_r13) / 4,
112	offsetof(struct trapframe, tf_r14) / 4,
113	offsetof(struct trapframe, tf_r15) / 4,
114	offsetof(struct trapframe, tf_r16) / 4,
115	offsetof(struct trapframe, tf_r17) / 4,
116	offsetof(struct trapframe, tf_r18) / 4,
117	offsetof(struct trapframe, tf_t4) / 4,
118	offsetof(struct trapframe, tf_t3) / 4,
119	offsetof(struct trapframe, tf_t2) / 4,
120	offsetof(struct trapframe, tf_t1) / 4,
121	offsetof(struct trapframe, tf_arg3) / 4,
122	offsetof(struct trapframe, tf_arg2) / 4,
123	offsetof(struct trapframe, tf_arg1) / 4,
124	offsetof(struct trapframe, tf_arg0) / 4,
125	offsetof(struct trapframe, tf_dp) / 4,
126	offsetof(struct trapframe, tf_ret0) / 4,
127	offsetof(struct trapframe, tf_ret1) / 4,
128	offsetof(struct trapframe, tf_sp) / 4,
129	offsetof(struct trapframe, tf_r31) / 4,
130};
131
132void
133userret(struct proc *p)
134{
135	struct cpu_info *ci = curcpu();
136	int sig;
137
138	if (p->p_md.md_astpending) {
139		p->p_md.md_astpending = 0;
140		uvmexp.softs++;
141		if (p->p_flag & P_OWEUPC) {
142			KERNEL_PROC_LOCK(p);
143			ADDUPROF(p);
144			KERNEL_PROC_UNLOCK(p);
145		}
146		if (ci->ci_want_resched)
147			preempt(NULL);
148	}
149
150	while ((sig = CURSIG(p)) != 0)
151		postsig(sig);
152
153	p->p_cpu->ci_schedstate.spc_curpriority = p->p_priority = p->p_usrpri;
154}
155
156void
157trap(type, frame)
158	int type;
159	struct trapframe *frame;
160{
161	struct cpu_info *ci = curcpu();
162	struct proc *p = curproc;
163	vaddr_t va;
164	struct vm_map *map;
165	struct vmspace *vm;
166	register vm_prot_t vftype;
167	register pa_space_t space;
168	union sigval sv;
169	u_int opcode;
170	int ret, trapnum;
171	const char *tts;
172	vm_fault_t fault = VM_FAULT_INVALID;
173#ifdef DIAGNOSTIC
174	int oldcpl = ci->ci_cpl;
175#endif
176
177	trapnum = type & ~T_USER;
178	opcode = frame->tf_iir;
179	if (trapnum <= T_EXCEPTION || trapnum == T_HIGHERPL ||
180	    trapnum == T_LOWERPL || trapnum == T_TAKENBR ||
181	    trapnum == T_IDEBUG || trapnum == T_PERFMON) {
182		va = frame->tf_iioq_head;
183		space = frame->tf_iisq_head;
184		vftype = UVM_PROT_EXEC;
185	} else {
186		va = frame->tf_ior;
187		space = frame->tf_isr;
188		if (va == frame->tf_iioq_head)
189			vftype = UVM_PROT_EXEC;
190		else if (inst_store(opcode))
191			vftype = UVM_PROT_WRITE;
192		else
193			vftype = UVM_PROT_READ;
194	}
195
196	if (frame->tf_flags & TFF_LAST)
197		p->p_md.md_regs = frame;
198
199	if (trapnum > trap_types)
200		tts = "reserved";
201	else
202		tts = trap_type[trapnum];
203
204#ifdef TRAPDEBUG
205	if (trapnum != T_INTERRUPT && trapnum != T_IBREAK)
206		db_printf("trap: %x, %s for %x:%x at %x:%x, fl=%x, fp=%p\n",
207		    type, tts, space, va, frame->tf_iisq_head,
208		    frame->tf_iioq_head, frame->tf_flags, frame);
209	else if (trapnum  == T_IBREAK)
210		db_printf("trap: break instruction %x:%x at %x:%x, fp=%p\n",
211		    break5(opcode), break13(opcode),
212		    frame->tf_iisq_head, frame->tf_iioq_head, frame);
213
214	{
215		extern int etext;
216		if (frame < (struct trapframe *)&etext) {
217			printf("trap: bogus frame ptr %p\n", frame);
218			goto dead_end;
219		}
220	}
221#endif
222	if (trapnum != T_INTERRUPT) {
223		uvmexp.traps++;
224		mtctl(frame->tf_eiem, CR_EIEM);
225	}
226
227	switch (type) {
228	case T_NONEXIST:
229	case T_NONEXIST | T_USER:
230		/* we've got screwed up by the central scrutinizer */
231		printf("trap: elvis has just left the building!\n");
232		goto dead_end;
233
234	case T_RECOVERY:
235	case T_RECOVERY | T_USER:
236		/* XXX will implement later */
237		printf("trap: handicapped");
238		goto dead_end;
239
240#ifdef DIAGNOSTIC
241	case T_EXCEPTION:
242		panic("FPU/SFU emulation botch");
243
244		/* these just can't happen ever */
245	case T_PRIV_OP:
246	case T_PRIV_REG:
247		/* these just can't make it to the trap() ever */
248	case T_HPMC:
249	case T_HPMC | T_USER:
250#endif
251	case T_IBREAK:
252	case T_DATALIGN:
253	case T_DBREAK:
254	dead_end:
255#ifdef DDB
256		if (kdb_trap (type, va, frame)) {
257			if (type == T_IBREAK) {
258				/* skip break instruction */
259				frame->tf_iioq_head = frame->tf_iioq_tail;
260				frame->tf_iioq_tail += 4;
261			}
262			return;
263		}
264#else
265		if (type == T_DATALIGN || type == T_DPROT)
266			panic ("trap: %s at 0x%x", tts, va);
267		else
268			panic ("trap: no debugger for \"%s\" (%d)", tts, type);
269#endif
270		break;
271
272	case T_IBREAK | T_USER:
273	case T_DBREAK | T_USER: {
274		int code = TRAP_BRKPT;
275#ifdef PTRACE
276		ss_clear_breakpoints(p);
277		if (opcode == SSBREAKPOINT)
278			code = TRAP_TRACE;
279#endif
280		/* pass to user debugger */
281		KERNEL_PROC_LOCK(p);
282		trapsignal(p, SIGTRAP, type &~ T_USER, code, sv);
283		KERNEL_PROC_UNLOCK(p);
284		}
285		break;
286
287#ifdef PTRACE
288	case T_TAKENBR | T_USER:
289		ss_clear_breakpoints(p);
290
291		/* pass to user debugger */
292		KERNEL_PROC_LOCK(p);
293		trapsignal(p, SIGTRAP, type &~ T_USER, TRAP_TRACE, sv);
294		KERNEL_PROC_UNLOCK(p);
295		break;
296#endif
297
298	case T_EXCEPTION | T_USER: {
299		u_int64_t *fpp = (u_int64_t *)frame->tf_cr30;
300		u_int32_t *pex;
301		int i, flt;
302
303		pex = (u_int32_t *)&fpp[0];
304		for (i = 0, pex++; i < 7 && !*pex; i++, pex++);
305		flt = 0;
306		if (i < 7) {
307			u_int32_t stat = HPPA_FPU_OP(*pex);
308			if (stat & HPPA_FPU_UNMPL)
309				flt = FPE_FLTINV;
310			else if (stat & (HPPA_FPU_V << 1))
311				flt = FPE_FLTINV;
312			else if (stat & (HPPA_FPU_Z << 1))
313				flt = FPE_FLTDIV;
314			else if (stat & (HPPA_FPU_I << 1))
315				flt = FPE_FLTRES;
316			else if (stat & (HPPA_FPU_O << 1))
317				flt = FPE_FLTOVF;
318			else if (stat & (HPPA_FPU_U << 1))
319				flt = FPE_FLTUND;
320			/* still left: under/over-flow w/ inexact */
321
322			/* cleanup exceptions (XXX deliver all ?) */
323			while (i++ < 7)
324				*pex++ = 0;
325		}
326		/* reset the trap flag, as if there was none */
327		fpp[0] &= ~(((u_int64_t)HPPA_FPU_T) << 32);
328
329		sv.sival_int = va;
330		KERNEL_PROC_LOCK(p);
331		trapsignal(p, SIGFPE, type &~ T_USER, flt, sv);
332		KERNEL_PROC_UNLOCK(p);
333		}
334		break;
335
336	case T_EMULATION:
337		panic("trap: emulation trap in the kernel");
338		break;
339
340	case T_EMULATION | T_USER:
341		sv.sival_int = va;
342		KERNEL_PROC_LOCK(p);
343		trapsignal(p, SIGILL, type &~ T_USER, ILL_COPROC, sv);
344		KERNEL_PROC_UNLOCK(p);
345		break;
346
347	case T_OVERFLOW | T_USER:
348		sv.sival_int = va;
349		KERNEL_PROC_LOCK(p);
350		trapsignal(p, SIGFPE, type &~ T_USER, FPE_INTOVF, sv);
351		KERNEL_PROC_UNLOCK(p);
352		break;
353
354	case T_CONDITION | T_USER:
355		sv.sival_int = va;
356		KERNEL_PROC_LOCK(p);
357		trapsignal(p, SIGFPE, type &~ T_USER, FPE_INTDIV, sv);
358		KERNEL_PROC_UNLOCK(p);
359		break;
360
361	case T_PRIV_OP | T_USER:
362		sv.sival_int = va;
363		KERNEL_PROC_LOCK(p);
364		trapsignal(p, SIGILL, type &~ T_USER, ILL_PRVOPC, sv);
365		KERNEL_PROC_UNLOCK(p);
366		break;
367
368	case T_PRIV_REG | T_USER:
369		sv.sival_int = va;
370		KERNEL_PROC_LOCK(p);
371		trapsignal(p, SIGILL, type &~ T_USER, ILL_PRVREG, sv);
372		KERNEL_PROC_UNLOCK(p);
373		break;
374
375		/* these should never got here */
376	case T_HIGHERPL | T_USER:
377	case T_LOWERPL | T_USER:
378		sv.sival_int = va;
379		KERNEL_PROC_LOCK(p);
380		trapsignal(p, SIGSEGV, vftype, SEGV_ACCERR, sv);
381		KERNEL_PROC_UNLOCK(p);
382		break;
383
384	/*
385	 * On PCXS processors, traps T_DATACC, T_DATAPID and T_DATALIGN
386	 * are shared.  We need to sort out the unaligned access situation
387	 * first, before handling this trap as T_DATACC.
388	 */
389	case T_DPROT | T_USER:
390		if (cpu_type == hpcxs) {
391			if (pcxs_unaligned(opcode, va))
392				goto datalign_user;
393			else
394				goto datacc;
395		}
396		/* FALLTHROUGH */
397
398	case T_IPROT | T_USER:
399		sv.sival_int = va;
400		KERNEL_PROC_LOCK(p);
401		trapsignal(p, SIGSEGV, vftype, SEGV_ACCERR, sv);
402		KERNEL_PROC_UNLOCK(p);
403		break;
404
405	case T_ITLBMISSNA:
406	case T_ITLBMISSNA | T_USER:
407	case T_DTLBMISSNA:
408	case T_DTLBMISSNA | T_USER:
409		if (space == HPPA_SID_KERNEL)
410			map = kernel_map;
411		else {
412			vm = p->p_vmspace;
413			map = &vm->vm_map;
414		}
415
416		if ((opcode & 0xfc003fc0) == 0x04001340) {
417			/* lpa failure case */
418			frame_regmap(frame, opcode & 0x1f) = 0;
419			frame->tf_ipsw |= PSL_N;
420		} else if ((opcode & 0xfc001f80) == 0x04001180) {
421			int pl;
422
423			/* dig probe[rw]i? insns */
424			if (opcode & 0x2000)
425				pl = (opcode >> 16) & 3;
426			else
427				pl = frame_regmap(frame,
428				    (opcode >> 16) & 0x1f) & 3;
429
430			if (type & T_USER)
431				KERNEL_PROC_LOCK(p);
432			else
433				KERNEL_LOCK();
434
435			if ((type & T_USER && space == HPPA_SID_KERNEL) ||
436			    (frame->tf_iioq_head & 3) != pl ||
437			    (type & T_USER && va >= VM_MAXUSER_ADDRESS) ||
438			    uvm_fault(map, trunc_page(va), fault,
439			     opcode & 0x40? UVM_PROT_WRITE : UVM_PROT_READ)) {
440				frame_regmap(frame, opcode & 0x1f) = 0;
441				frame->tf_ipsw |= PSL_N;
442			}
443
444			if (type & T_USER)
445				KERNEL_PROC_UNLOCK(p);
446			else
447				KERNEL_UNLOCK();
448		} else if (type & T_USER) {
449			sv.sival_int = va;
450			KERNEL_PROC_LOCK(p);
451			trapsignal(p, SIGILL, type & ~T_USER, ILL_ILLTRP, sv);
452			KERNEL_PROC_UNLOCK(p);
453		} else
454			panic("trap: %s @ 0x%x:0x%x for 0x%x:0x%x irr 0x%08x",
455			    tts, frame->tf_iisq_head, frame->tf_iioq_head,
456			    space, va, opcode);
457		break;
458
459	case T_TLB_DIRTY:
460	case T_TLB_DIRTY | T_USER:
461	case T_DATACC:
462	case T_DATACC | T_USER:
463datacc:
464		fault = VM_FAULT_PROTECT;
465	case T_ITLBMISS:
466	case T_ITLBMISS | T_USER:
467	case T_DTLBMISS:
468	case T_DTLBMISS | T_USER:
469		/*
470		 * it could be a kernel map for exec_map faults
471		 */
472		if (space == HPPA_SID_KERNEL)
473			map = kernel_map;
474		else {
475			vm = p->p_vmspace;
476			map = &vm->vm_map;
477		}
478
479		/*
480		 * user faults out of user addr space are always a fail,
481		 * this happens on va >= VM_MAXUSER_ADDRESS, where
482		 * space id will be zero and therefore cause
483		 * a misbehave lower in the code.
484		 *
485		 * also check that faulted space id matches the curproc.
486		 */
487		if ((type & T_USER && va >= VM_MAXUSER_ADDRESS) ||
488		   (type & T_USER && map->pmap->pm_space != space)) {
489			sv.sival_int = va;
490			KERNEL_PROC_LOCK(p);
491			trapsignal(p, SIGSEGV, vftype, SEGV_MAPERR, sv);
492			KERNEL_PROC_UNLOCK(p);
493			break;
494		}
495
496		if (type & T_USER)
497			KERNEL_PROC_LOCK(p);
498		else
499			KERNEL_LOCK();
500
501		ret = uvm_fault(map, trunc_page(va), fault, vftype);
502
503		/*
504		 * If this was a stack access we keep track of the maximum
505		 * accessed stack size.  Also, if uvm_fault gets a protection
506		 * failure it is due to accessing the stack region outside
507		 * the current limit and we need to reflect that as an access
508		 * error.
509		 */
510		if (space != HPPA_SID_KERNEL &&
511		    va < (vaddr_t)vm->vm_minsaddr) {
512			if (ret == 0)
513				uvm_grow(p, va);
514			else if (ret == EACCES)
515				ret = EFAULT;
516		}
517
518		if (type & T_USER)
519			KERNEL_PROC_UNLOCK(p);
520		else
521			KERNEL_UNLOCK();
522
523		if (ret != 0) {
524			if (type & T_USER) {
525				sv.sival_int = va;
526				KERNEL_PROC_LOCK(p);
527				trapsignal(p, SIGSEGV, vftype,
528				    ret == EACCES? SEGV_ACCERR : SEGV_MAPERR,
529				    sv);
530				KERNEL_PROC_UNLOCK(p);
531			} else {
532				if (p && p->p_addr->u_pcb.pcb_onfault) {
533					frame->tf_iioq_tail = 4 +
534					    (frame->tf_iioq_head =
535						p->p_addr->u_pcb.pcb_onfault);
536#ifdef DDB
537					frame->tf_iir = 0;
538#endif
539				} else {
540					panic("trap: "
541					    "uvm_fault(%p, %lx, %d, %d): %d",
542					    map, va, fault, vftype, ret);
543				}
544			}
545		}
546		break;
547
548	case T_DATALIGN | T_USER:
549datalign_user:
550		sv.sival_int = va;
551		KERNEL_PROC_LOCK(p);
552		trapsignal(p, SIGBUS, vftype, BUS_ADRALN, sv);
553		KERNEL_PROC_UNLOCK(p);
554		break;
555
556	case T_INTERRUPT:
557	case T_INTERRUPT | T_USER:
558		cpu_intr(frame);
559		break;
560
561	case T_CONDITION:
562		panic("trap: divide by zero in the kernel");
563		break;
564
565	case T_ILLEGAL:
566	case T_ILLEGAL | T_USER:
567		/* see if it's a SPOP1,,0 */
568		if ((opcode & 0xfffffe00) == 0x10000200) {
569			frame_regmap(frame, opcode & 0x1f) = 0;
570			frame->tf_ipsw |= PSL_N;
571			break;
572		}
573		if (type & T_USER) {
574			sv.sival_int = va;
575			KERNEL_PROC_LOCK(p);
576			trapsignal(p, SIGILL, type &~ T_USER, ILL_ILLOPC, sv);
577			KERNEL_PROC_UNLOCK(p);
578			break;
579		}
580		/* FALLTHROUGH */
581
582	/*
583	 * On PCXS processors, traps T_DATACC, T_DATAPID and T_DATALIGN
584	 * are shared.  We need to sort out the unaligned access situation
585	 * first, before handling this trap as T_DATACC.
586	 */
587	case T_DPROT:
588		if (cpu_type == hpcxs) {
589			if (pcxs_unaligned(opcode, va))
590				goto dead_end;
591			else
592				goto datacc;
593		}
594		/* FALLTHROUGH to unimplemented */
595
596	case T_LOWERPL:
597	case T_IPROT:
598	case T_OVERFLOW:
599	case T_HIGHERPL:
600	case T_TAKENBR:
601	case T_POWERFAIL:
602	case T_LPMC:
603	case T_PAGEREF:
604	case T_DATAPID:
605	case T_DATAPID | T_USER:
606		/* FALLTHROUGH to unimplemented */
607	default:
608#if 0
609if (kdb_trap (type, va, frame))
610	return;
611#endif
612		panic("trap: unimplemented \'%s\' (%d)", tts, trapnum);
613	}
614
615#ifdef DIAGNOSTIC
616	if (ci->ci_cpl != oldcpl)
617		printf("WARNING: SPL (%d) NOT LOWERED ON "
618		    "TRAP (%d) EXIT\n", ci->ci_cpl, trapnum);
619#endif
620
621	if (trapnum != T_INTERRUPT)
622		splx(ci->ci_cpl);	/* process softints */
623
624	/*
625	 * in case we were interrupted from the syscall gate page
626	 * treat this as we were not really running user code no more
627	 * for weird things start to happen on return to the userland
628	 * and also see a note in locore.S:TLABEL(all)
629	 */
630	if ((type & T_USER) && !(frame->tf_iisq_head == HPPA_SID_KERNEL &&
631	    (frame->tf_iioq_head & ~PAGE_MASK) == SYSCALLGATE))
632		userret(p);
633}
634
635void
636child_return(void *arg)
637{
638	struct proc *p = (struct proc *)arg;
639	struct trapframe *tf = p->p_md.md_regs;
640
641	/*
642	 * Set up return value registers as libc:fork() expects
643	 */
644	tf->tf_ret0 = 0;
645	tf->tf_ret1 = 1;	/* ischild */
646	tf->tf_t1 = 0;		/* errno */
647
648	KERNEL_PROC_UNLOCK(p);
649
650	userret(p);
651#ifdef KTRACE
652	if (KTRPOINT(p, KTR_SYSRET)) {
653		KERNEL_PROC_LOCK(p);
654		ktrsysret(p,
655		    (p->p_flag & P_PPWAIT) ? SYS_vfork : SYS_fork, 0, 0);
656		KERNEL_PROC_UNLOCK(p);
657	}
658#endif
659}
660
661#ifdef PTRACE
662
663#include <sys/ptrace.h>
664
665int
666ss_get_value(struct proc *p, vaddr_t addr, u_int *value)
667{
668	struct uio uio;
669	struct iovec iov;
670
671	iov.iov_base = (caddr_t)value;
672	iov.iov_len = sizeof(u_int);
673	uio.uio_iov = &iov;
674	uio.uio_iovcnt = 1;
675	uio.uio_offset = (off_t)addr;
676	uio.uio_resid = sizeof(u_int);
677	uio.uio_segflg = UIO_SYSSPACE;
678	uio.uio_rw = UIO_READ;
679	uio.uio_procp = curproc;
680	return (process_domem(curproc, p, &uio, PT_READ_I));
681}
682
683int
684ss_put_value(struct proc *p, vaddr_t addr, u_int value)
685{
686	struct uio uio;
687	struct iovec iov;
688
689	iov.iov_base = (caddr_t)&value;
690	iov.iov_len = sizeof(u_int);
691	uio.uio_iov = &iov;
692	uio.uio_iovcnt = 1;
693	uio.uio_offset = (off_t)addr;
694	uio.uio_resid = sizeof(u_int);
695	uio.uio_segflg = UIO_SYSSPACE;
696	uio.uio_rw = UIO_WRITE;
697	uio.uio_procp = curproc;
698	return (process_domem(curproc, p, &uio, PT_WRITE_I));
699}
700
701void
702ss_clear_breakpoints(struct proc *p)
703{
704	/* Restore origional instructions. */
705	if (p->p_md.md_bpva != 0) {
706		ss_put_value(p, p->p_md.md_bpva, p->p_md.md_bpsave[0]);
707		ss_put_value(p, p->p_md.md_bpva + 4, p->p_md.md_bpsave[1]);
708		p->p_md.md_bpva = 0;
709	}
710}
711
712int
713process_sstep(struct proc *p, int sstep)
714{
715	int error;
716
717	ss_clear_breakpoints(p);
718
719	/* Don't touch the syscall gateway page. */
720	if (sstep == 0 ||
721	    (p->p_md.md_regs->tf_iioq_tail & ~PAGE_MASK) == SYSCALLGATE) {
722		p->p_md.md_regs->tf_ipsw &= ~PSL_T;
723		return (0);
724	}
725
726	p->p_md.md_bpva = p->p_md.md_regs->tf_iioq_tail & ~HPPA_PC_PRIV_MASK;
727
728	/*
729	 * Insert two breakpoint instructions; the first one might be
730	 * nullified.  Of course we need to save two instruction
731	 * first.
732	 */
733
734	error = ss_get_value(p, p->p_md.md_bpva, &p->p_md.md_bpsave[0]);
735	if (error)
736		return (error);
737	error = ss_get_value(p, p->p_md.md_bpva + 4, &p->p_md.md_bpsave[1]);
738	if (error)
739		return (error);
740
741	error = ss_put_value(p, p->p_md.md_bpva, SSBREAKPOINT);
742	if (error)
743		return (error);
744	error = ss_put_value(p, p->p_md.md_bpva + 4, SSBREAKPOINT);
745	if (error)
746		return (error);
747
748	p->p_md.md_regs->tf_ipsw |= PSL_T;
749	return (0);
750}
751
752#endif	/* PTRACE */
753
754/*
755 * call actual syscall routine
756 */
757void
758syscall(struct trapframe *frame)
759{
760	struct cpu_info *ci = curcpu();
761	register struct proc *p = curproc;
762	register const struct sysent *callp;
763	int retq, nsys, code, argsize, argoff, oerror, error;
764	register_t args[8], rval[2];
765#ifdef DIAGNOSTIC
766	int oldcpl = ci->ci_cpl;
767#endif
768
769	uvmexp.syscalls++;
770
771	if (!USERMODE(frame->tf_iioq_head))
772		panic("syscall");
773
774	p->p_md.md_regs = frame;
775	nsys = p->p_emul->e_nsysent;
776	callp = p->p_emul->e_sysent;
777
778	argoff = 4; retq = 0;
779	switch (code = frame->tf_t1) {
780	case SYS_syscall:
781		code = frame->tf_arg0;
782		args[0] = frame->tf_arg1;
783		args[1] = frame->tf_arg2;
784		args[2] = frame->tf_arg3;
785		argoff = 3;
786		break;
787	case SYS___syscall:
788		if (callp != sysent)
789			break;
790		/*
791		 * this works, because quads get magically swapped
792		 * due to the args being laid backwards on the stack
793		 * and then copied in words
794		 */
795		code = frame->tf_arg0;
796		args[0] = frame->tf_arg2;
797		args[1] = frame->tf_arg3;
798		argoff = 2;
799		retq = 1;
800		break;
801	default:
802		args[0] = frame->tf_arg0;
803		args[1] = frame->tf_arg1;
804		args[2] = frame->tf_arg2;
805		args[3] = frame->tf_arg3;
806		break;
807	}
808
809	if (code < 0 || code >= nsys)
810		callp += p->p_emul->e_nosys;	/* bad syscall # */
811	else
812		callp += code;
813
814	oerror = error = 0;
815	if ((argsize = callp->sy_argsize)) {
816		int i;
817
818		for (i = 0, argsize -= argoff * 4;
819		    argsize > 0; i++, argsize -= 4) {
820			error = copyin((void *)(frame->tf_sp +
821			    HPPA_FRAME_ARG(i + 4)), args + i + argoff, 4);
822
823			if (error)
824				break;
825		}
826
827		/*
828		 * coming from syscall() or __syscall we must be
829		 * having one of those w/ a 64 bit arguments,
830		 * which needs a word swap due to the order
831		 * of the arguments on the stack.
832		 * this assumes that none of 'em are called
833		 * by their normal syscall number, maybe a regress
834		 * test should be used, to watch the behaviour.
835		 */
836		if (!error && argoff < 4) {
837			int t;
838
839			i = 0;
840			switch (code) {
841			case SYS_lseek:		retq = 0;
842			case SYS_truncate:
843			case SYS_ftruncate:	i = 2;	break;
844			case SYS_preadv:
845			case SYS_pwritev:
846			case SYS_pread:
847			case SYS_pwrite:	i = 4;	break;
848			case SYS_mquery:
849			case SYS_mmap:		i = 6;	break;
850			}
851
852			if (i) {
853				t = args[i];
854				args[i] = args[i + 1];
855				args[i + 1] = t;
856			}
857		}
858	}
859
860#ifdef SYSCALL_DEBUG
861	KERNEL_PROC_LOCK(p);
862	scdebug_call(p, code, args);
863	KERNEL_PROC_UNLOCK(p);
864#endif
865#ifdef KTRACE
866	if (KTRPOINT(p, KTR_SYSCALL)) {
867		KERNEL_PROC_LOCK(p);
868		ktrsyscall(p, code, callp->sy_argsize, args);
869		KERNEL_PROC_UNLOCK(p);
870	}
871#endif
872	if (error)
873		goto bad;
874
875	rval[0] = 0;
876	rval[1] = frame->tf_ret1;
877#if NSYSTRACE > 0
878	if (ISSET(p->p_flag, P_SYSTRACE)) {
879		KERNEL_PROC_LOCK(p);
880		oerror = error = systrace_redirect(code, p, args, rval);
881		KERNEL_PROC_UNLOCK(p);
882	} else
883#endif
884	{
885		int nolock = (callp->sy_flags & SY_NOLOCK);
886		if (!nolock)
887			KERNEL_PROC_LOCK(p);
888		oerror = error = (*callp->sy_call)(p, args, rval);
889		if (!nolock)
890			KERNEL_PROC_UNLOCK(p);
891
892	}
893	switch (error) {
894	case 0:
895		frame->tf_ret0 = rval[0];
896		frame->tf_ret1 = rval[!retq];
897		frame->tf_t1 = 0;
898		break;
899	case ERESTART:
900		frame->tf_iioq_head -= 12;
901		frame->tf_iioq_tail -= 12;
902	case EJUSTRETURN:
903		break;
904	default:
905	bad:
906		if (p->p_emul->e_errno)
907			error = p->p_emul->e_errno[error];
908		frame->tf_t1 = error;
909		frame->tf_ret0 = error;
910		frame->tf_ret1 = 0;
911		break;
912	}
913#ifdef SYSCALL_DEBUG
914	KERNEL_PROC_LOCK(p);
915	scdebug_ret(p, code, oerror, rval);
916	KERNEL_PROC_UNLOCK(p);
917#endif
918	userret(p);
919#ifdef KTRACE
920	if (KTRPOINT(p, KTR_SYSRET)) {
921		KERNEL_PROC_LOCK(p);
922		ktrsysret(p, code, oerror, rval[0]);
923		KERNEL_PROC_UNLOCK(p);
924	}
925#endif
926#ifdef DIAGNOSTIC
927	if (ci->ci_cpl != oldcpl) {
928		printf("WARNING: SPL (0x%x) NOT LOWERED ON "
929		    "syscall(0x%x, 0x%x, 0x%x, 0x%x...) EXIT, PID %d\n",
930		    ci->ci_cpl, code, args[0], args[1], args[2], p->p_pid);
931		ci->ci_cpl = oldcpl;
932	}
933#endif
934	splx(ci->ci_cpl);	/* process softints */
935}
936
937/*
938 * Decide if opcode `opcode' accessing virtual address `va' caused an
939 * unaligned trap. Returns zero if the access is correctly aligned.
940 * Used on PCXS processors to sort out exception causes.
941 */
942int
943pcxs_unaligned(u_int opcode, vaddr_t va)
944{
945	u_int mbz_bits;
946
947	/*
948	 * Exit early if the va is obviously aligned enough.
949	 */
950	if ((va & 0x0f) == 0)
951		return 0;
952
953	mbz_bits = 0;
954
955	/*
956	 * Only load and store instructions can cause unaligned access.
957	 * There are three opcode patterns to look for:
958	 * - canonical load/store
959	 * - load/store short or indexed
960	 * - coprocessor load/store
961	 */
962
963	if ((opcode & 0xd0000000) == 0x40000000) {
964		switch ((opcode >> 26) & 0x03) {
965		case 0x00:	/* ldb, stb */
966			mbz_bits = 0x00;
967			break;
968		case 0x01:	/* ldh, sth */
969			mbz_bits = 0x01;
970			break;
971		case 0x02:	/* ldw, stw */
972		case 0x03:	/* ldwm, stwm */
973			mbz_bits = 0x03;
974			break;
975		}
976	} else
977
978	if ((opcode & 0xfc000000) == 0x0c000000) {
979		switch ((opcode >> 6) & 0x0f) {
980		case 0x01:	/* ldhx, ldhs */
981			mbz_bits = 0x01;
982			break;
983		case 0x02:	/* ldwx, ldws */
984			mbz_bits = 0x03;
985			break;
986		case 0x07:	/* ldcwx, ldcws */
987			mbz_bits = 0x0f;
988			break;
989		case 0x09:
990			if ((opcode & (1 << 12)) != 0)	/* sths */
991				mbz_bits = 0x01;
992			break;
993		case 0x0a:
994			if ((opcode & (1 << 12)) != 0)	/* stws */
995				mbz_bits = 0x03;
996			break;
997		}
998	} else
999
1000	if ((opcode & 0xf4000000) == 0x24000000) {
1001		if ((opcode & (1 << 27)) != 0) {
1002			/* cldwx, cstwx, cldws, cstws */
1003			mbz_bits = 0x03;
1004		} else {
1005			/* clddx, cstdx, cldds, cstds */
1006			mbz_bits = 0x07;
1007		}
1008	}
1009
1010	return (va & mbz_bits);
1011}
1012