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