trap.c revision 1.9
1/*	$OpenBSD: trap.c,v 1.9 2004/07/22 18:58:57 miod Exp $	*/
2/*
3 * Copyright (c) 2004, Miodrag Vallat.
4 * Copyright (c) 1998 Steve Murphree, Jr.
5 * Copyright (c) 1996 Nivas Madhur
6 * All rights reserved.
7 *
8 * Redistribution and use in source and binary forms, with or without
9 * modification, are permitted provided that the following conditions
10 * are met:
11 * 1. Redistributions of source code must retain the above copyright
12 *    notice, this list of conditions and the following disclaimer.
13 * 2. Redistributions in binary form must reproduce the above copyright
14 *    notice, this list of conditions and the following disclaimer in the
15 *    documentation and/or other materials provided with the distribution.
16 * 3. All advertising materials mentioning features or use of this software
17 *    must display the following acknowledgement:
18 *      This product includes software developed by Nivas Madhur.
19 * 4. The name of the author may not be used to endorse or promote products
20 *    derived from this software without specific prior written permission
21 *
22 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
23 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
24 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
25 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
26 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
27 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
28 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
29 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
30 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
31 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
32 *
33 */
34/*
35 * Mach Operating System
36 * Copyright (c) 1991 Carnegie Mellon University
37 * Copyright (c) 1991 OMRON Corporation
38 * All Rights Reserved.
39 *
40 * Permission to use, copy, modify and distribute this software and its
41 * documentation is hereby granted, provided that both the copyright
42 * notice and this permission notice appear in all copies of the
43 * software, derivative works or modified versions, and any portions
44 * thereof, and that both notices appear in supporting documentation.
45 *
46 */
47
48#include <sys/types.h>
49#include <sys/param.h>
50#include <sys/proc.h>
51#include <sys/signalvar.h>
52#include <sys/user.h>
53#include <sys/syscall.h>
54#include <sys/systm.h>
55#include <sys/ktrace.h>
56
57#include "systrace.h"
58#include <dev/systrace.h>
59
60#include <uvm/uvm_extern.h>
61
62#include <machine/asm_macro.h>   /* enable/disable interrupts */
63#include <machine/cpu.h>
64#include <machine/locore.h>
65#ifdef M88100
66#include <machine/m88100.h>		/* DMT_xxx */
67#include <machine/m8820x.h>		/* CMMU_PFSR_xxx */
68#endif
69#ifdef M88110
70#include <machine/m88110.h>
71#endif
72#include <machine/pcb.h>		/* FIP_E, etc. */
73#include <machine/psl.h>		/* FIP_E, etc. */
74#include <machine/trap.h>
75
76#include <machine/db_machdep.h>
77
78#define SSBREAKPOINT (0xF000D1F8U) /* Single Step Breakpoint */
79
80#define USERMODE(PSR)   (((PSR) & PSR_MODE) == 0)
81#define SYSTEMMODE(PSR) (((PSR) & PSR_MODE) != 0)
82
83/* sigh */
84extern int procfs_domem(struct proc *, struct proc *, void *, struct uio *);
85
86__dead void panictrap(int, struct trapframe *);
87__dead void error_fatal(struct trapframe *);
88int double_reg_fixup(struct trapframe *);
89
90extern void regdump(struct trapframe *f);
91
92const char *trap_type[] = {
93	"Reset",
94	"Interrupt Exception",
95	"Instruction Access",
96	"Data Access Exception",
97	"Misaligned Access",
98	"Unimplemented Opcode",
99	"Privilege Violation"
100	"Bounds Check Violation",
101	"Illegal Integer Divide",
102	"Integer Overflow",
103	"Error Exception",
104	"Non-Maskable Exception",
105};
106const int trap_types = sizeof trap_type / sizeof trap_type[0];
107
108const char *pbus_exception_type[] = {
109	"Success (No Fault)",
110	"unknown 1",
111	"unknown 2",
112	"Bus Error",
113	"Segment Fault",
114	"Page Fault",
115	"Supervisor Violation",
116	"Write Violation",
117};
118
119static inline void
120userret(struct proc *p, struct trapframe *frame, u_quad_t oticks)
121{
122	int sig;
123
124	/* take pending signals */
125	while ((sig = CURSIG(p)) != 0)
126		postsig(sig);
127	p->p_priority = p->p_usrpri;
128
129	if (want_resched) {
130		/*
131		 * We're being preempted.
132		 */
133		preempt(NULL);
134		while ((sig = CURSIG(p)) != 0)
135			postsig(sig);
136	}
137
138	/*
139	 * If profiling, charge recent system time to the trapped pc.
140	 */
141	if (p->p_flag & P_PROFIL) {
142		extern int psratio;
143
144		addupc_task(p, frame->tf_sxip & XIP_ADDR,
145		    (int)(p->p_sticks - oticks) * psratio);
146	}
147	curpriority = p->p_priority;
148}
149
150__dead void
151panictrap(int type, struct trapframe *frame)
152{
153	static int panicing = 0;
154
155	if (panicing++ == 0) {
156		switch (cputyp) {
157#ifdef M88100
158		case CPU_88100:
159			if (type == 2) {
160				/* instruction exception */
161				printf("\nInstr access fault (%s) v = %x, "
162				    "frame %p\n",
163				    pbus_exception_type[
164				      CMMU_PFSR_FAULT(frame->tf_ipfsr)],
165				    frame->tf_sxip & XIP_ADDR, frame);
166			} else if (type == 3) {
167				/* data access exception */
168				printf("\nData access fault (%s) v = %x, "
169				    "frame %p\n",
170				    pbus_exception_type[
171				      CMMU_PFSR_FAULT(frame->tf_dpfsr)],
172				    frame->tf_sxip & XIP_ADDR, frame);
173			} else
174				printf("\nTrap type %d, v = %x, frame %p\n",
175				    type, frame->tf_sxip & XIP_ADDR, frame);
176			break;
177#endif
178#ifdef M88110
179		case CPU_88110:
180			printf("\nTrap type %d, v = %x, frame %p\n",
181			    type, frame->tf_exip, frame);
182			break;
183#endif
184		}
185#ifdef DDB
186		regdump(frame);
187#endif
188	}
189	if ((u_int)type < trap_types)
190		panic(trap_type[type]);
191	else
192		panic("trap %d", type);
193	/*NOTREACHED*/
194}
195
196#ifdef M88100
197void
198m88100_trap(unsigned type, struct trapframe *frame)
199{
200	struct proc *p;
201	u_quad_t sticks = 0;
202	struct vm_map *map;
203	vaddr_t va, pcb_onfault;
204	vm_prot_t ftype;
205	int fault_type, pbus_type;
206	u_long fault_code;
207	unsigned nss, fault_addr;
208	struct vmspace *vm;
209	union sigval sv;
210	int result;
211#ifdef DDB
212	int s;
213#endif
214	int sig = 0;
215
216	extern struct vm_map *kernel_map;
217	extern caddr_t guarded_access_start;
218	extern caddr_t guarded_access_end;
219	extern caddr_t guarded_access_bad;
220
221	uvmexp.traps++;
222	if ((p = curproc) == NULL)
223		p = &proc0;
224
225	if (USERMODE(frame->tf_epsr)) {
226		sticks = p->p_sticks;
227		type += T_USER;
228		p->p_md.md_tf = frame;	/* for ptrace/signals */
229	}
230	fault_type = 0;
231	fault_code = 0;
232	fault_addr = frame->tf_sxip & XIP_ADDR;
233
234	switch (type) {
235	default:
236		panictrap(frame->tf_vector, frame);
237		break;
238		/*NOTREACHED*/
239
240#if defined(DDB)
241	case T_KDB_BREAK:
242		s = splhigh();
243		db_enable_interrupt();
244		ddb_break_trap(T_KDB_BREAK, (db_regs_t*)frame);
245		db_disable_interrupt();
246		splx(s);
247		return;
248	case T_KDB_ENTRY:
249		s = splhigh();
250		db_enable_interrupt();
251		ddb_entry_trap(T_KDB_ENTRY, (db_regs_t*)frame);
252		db_disable_interrupt();
253		splx(s);
254		return;
255#endif /* DDB */
256	case T_ILLFLT:
257		printf("Unimplemented opcode!\n");
258		panictrap(frame->tf_vector, frame);
259		break;
260	case T_INT:
261	case T_INT+T_USER:
262		/* This function pointer is set in machdep.c
263		   It calls m188_ext_int or sbc_ext_int depending
264		   on the value of brdtyp - smurph */
265		(*md.interrupt_func)(T_INT, frame);
266		return;
267
268	case T_MISALGNFLT:
269		printf("kernel misaligned access exception @ 0x%08x\n",
270		    frame->tf_sxip);
271		panictrap(frame->tf_vector, frame);
272		break;
273
274	case T_INSTFLT:
275		/* kernel mode instruction access fault.
276		 * Should never, never happen for a non-paged kernel.
277		 */
278#ifdef TRAPDEBUG
279		pbus_type = CMMU_PFSR_FAULT(frame->tf_ipfsr);
280		printf("Kernel Instruction fault #%d (%s) v = 0x%x, frame 0x%x cpu %d\n",
281		    pbus_type, pbus_exception_type[pbus_type],
282		    fault_addr, frame, frame->tf_cpu);
283#endif
284		panictrap(frame->tf_vector, frame);
285		break;
286
287	case T_DATAFLT:
288		/* kernel mode data fault */
289
290		/* data fault on the user address? */
291		if ((frame->tf_dmt0 & DMT_DAS) == 0) {
292			type = T_DATAFLT + T_USER;
293			goto user_fault;
294		}
295
296		fault_addr = frame->tf_dma0;
297		if (frame->tf_dmt0 & (DMT_WRITE|DMT_LOCKBAR)) {
298			ftype = VM_PROT_READ|VM_PROT_WRITE;
299			fault_code = VM_PROT_WRITE;
300		} else {
301			ftype = VM_PROT_READ;
302			fault_code = VM_PROT_READ;
303		}
304
305		va = trunc_page((vaddr_t)fault_addr);
306		if (va == 0) {
307			panic("trap: bad kernel access at %x", fault_addr);
308		}
309
310		vm = p->p_vmspace;
311		map = kernel_map;
312
313		pbus_type = CMMU_PFSR_FAULT(frame->tf_dpfsr);
314#ifdef TRAPDEBUG
315		printf("Kernel Data access fault #%d (%s) v = 0x%x, frame 0x%x cpu %d\n",
316		    pbus_type, pbus_exception_type[pbus_type],
317		    fault_addr, frame, frame->tf_cpu);
318#endif
319
320		switch (pbus_type) {
321		case CMMU_PFSR_BERROR:
322			/*
323		 	 * If it is a guarded access, bus error is OK.
324		 	 */
325			if ((frame->tf_sxip & XIP_ADDR) >=
326			      (unsigned)&guarded_access_start &&
327			    (frame->tf_sxip & XIP_ADDR) <=
328			      (unsigned)&guarded_access_end) {
329				frame->tf_snip =
330				  ((unsigned)&guarded_access_bad    ) | NIP_V;
331				frame->tf_sfip =
332				  ((unsigned)&guarded_access_bad + 4) | FIP_V;
333				frame->tf_sxip = 0;
334				/* We sort of resolved the fault ourselves
335				 * because we know where it came from
336				 * [guarded_access()]. But we must still think
337				 * about the other possible transactions in
338				 * dmt1 & dmt2.  Mark dmt0 so that
339				 * data_access_emulation skips it.  XXX smurph
340				 */
341				frame->tf_dmt0 |= DMT_SKIP;
342				data_access_emulation((unsigned *)frame);
343				frame->tf_dpfsr = 0;
344				frame->tf_dmt0 = 0;
345				return;
346			}
347			break;
348		case CMMU_PFSR_SUCCESS:
349			/*
350			 * The fault was resolved. Call data_access_emulation
351			 * to drain the data unit pipe line and reset dmt0
352			 * so that trap won't get called again.
353			 */
354			data_access_emulation((unsigned *)frame);
355			frame->tf_dpfsr = 0;
356			frame->tf_dmt0 = 0;
357			return;
358		case CMMU_PFSR_SFAULT:
359		case CMMU_PFSR_PFAULT:
360			if ((pcb_onfault = p->p_addr->u_pcb.pcb_onfault) != 0)
361				p->p_addr->u_pcb.pcb_onfault = 0;
362			result = uvm_fault(map, va, VM_FAULT_INVALID, ftype);
363			p->p_addr->u_pcb.pcb_onfault = pcb_onfault;
364			if (result == 0) {
365				/*
366				 * We could resolve the fault. Call
367				 * data_access_emulation to drain the data
368				 * unit pipe line and reset dmt0 so that trap
369				 * won't get called again.
370				 */
371				data_access_emulation((unsigned *)frame);
372				frame->tf_dpfsr = 0;
373				frame->tf_dmt0 = 0;
374				return;
375			}
376			break;
377		}
378#ifdef TRAPDEBUG
379		printf("PBUS Fault %d (%s) va = 0x%x\n", pbus_type,
380		    pbus_exception_type[pbus_type], va);
381#endif
382		panictrap(frame->tf_vector, frame);
383		/* NOTREACHED */
384	case T_INSTFLT+T_USER:
385		/* User mode instruction access fault */
386		/* FALLTHROUGH */
387	case T_DATAFLT+T_USER:
388user_fault:
389		if (type == T_INSTFLT + T_USER) {
390			pbus_type = CMMU_PFSR_FAULT(frame->tf_ipfsr);
391#ifdef TRAPDEBUG
392			printf("User Instruction fault #%d (%s) v = 0x%x, frame 0x%x cpu %d\n",
393			    pbus_type, pbus_exception_type[pbus_type],
394			    fault_addr, frame, frame->tf_cpu);
395#endif
396		} else {
397			fault_addr = frame->tf_dma0;
398			pbus_type = CMMU_PFSR_FAULT(frame->tf_dpfsr);
399#ifdef TRAPDEBUG
400			printf("User Data access fault #%d (%s) v = 0x%x, frame 0x%x cpu %d\n",
401			    pbus_type, pbus_exception_type[pbus_type],
402			    fault_addr, frame, frame->tf_cpu);
403#endif
404		}
405
406		if (frame->tf_dmt0 & (DMT_WRITE | DMT_LOCKBAR)) {
407			ftype = VM_PROT_READ | VM_PROT_WRITE;
408			fault_code = VM_PROT_WRITE;
409		} else {
410			ftype = VM_PROT_READ;
411			fault_code = VM_PROT_READ;
412		}
413
414		va = trunc_page((vaddr_t)fault_addr);
415
416		vm = p->p_vmspace;
417		map = &vm->vm_map;
418		if ((pcb_onfault = p->p_addr->u_pcb.pcb_onfault) != 0)
419			p->p_addr->u_pcb.pcb_onfault = 0;
420
421		/* Call uvm_fault() to resolve non-bus error faults */
422		switch (pbus_type) {
423		case CMMU_PFSR_SUCCESS:
424			result = 0;
425			break;
426		case CMMU_PFSR_BERROR:
427			result = EACCES;
428			break;
429		default:
430			result = uvm_fault(map, va, VM_FAULT_INVALID, ftype);
431			if (result == EACCES)
432				result = EFAULT;
433			break;
434		}
435
436		p->p_addr->u_pcb.pcb_onfault = pcb_onfault;
437
438		if ((caddr_t)va >= vm->vm_maxsaddr) {
439			if (result == 0) {
440				nss = btoc(USRSTACK - va);/* XXX check this */
441				if (nss > vm->vm_ssize)
442					vm->vm_ssize = nss;
443			}
444		}
445
446		/*
447		 * This could be a fault caused in copyin*()
448		 * while accessing user space.
449		 */
450		if (result != 0 && pcb_onfault != 0) {
451			frame->tf_snip = pcb_onfault | NIP_V;
452			frame->tf_sfip = (pcb_onfault + 4) | FIP_V;
453			frame->tf_sxip = 0;
454			/*
455			 * Continue as if the fault had been resolved, but
456			 * do not try to complete the faulting access.
457			 */
458			frame->tf_dmt0 |= DMT_SKIP;
459			result = 0;
460		}
461
462		if (result == 0) {
463			if (type == T_DATAFLT+T_USER) {
464				/*
465			 	 * We could resolve the fault. Call
466			 	 * data_access_emulation to drain the data unit
467			 	 * pipe line and reset dmt0 so that trap won't
468			 	 * get called again.
469			 	 */
470				data_access_emulation((unsigned *)frame);
471				frame->tf_dpfsr = 0;
472				frame->tf_dmt0 = 0;
473			} else {
474				/*
475				 * back up SXIP, SNIP,
476				 * clearing the Error bit
477				 */
478				frame->tf_sfip = frame->tf_snip & ~FIP_E;
479				frame->tf_snip = frame->tf_sxip & ~NIP_E;
480				frame->tf_ipfsr = 0;
481			}
482		} else {
483			sig = result == EACCES ? SIGBUS : SIGSEGV;
484			fault_type = result == EACCES ?
485			    BUS_ADRERR : SEGV_MAPERR;
486		}
487		break;
488	case T_MISALGNFLT+T_USER:
489		/* Fix any misaligned ld.d or st.d instructions */
490		sig = double_reg_fixup(frame);
491		fault_type = BUS_ADRALN;
492		break;
493	case T_PRIVINFLT+T_USER:
494	case T_ILLFLT+T_USER:
495#ifndef DDB
496	case T_KDB_BREAK:
497	case T_KDB_ENTRY:
498#endif
499	case T_KDB_BREAK+T_USER:
500	case T_KDB_ENTRY+T_USER:
501	case T_KDB_TRACE:
502	case T_KDB_TRACE+T_USER:
503		sig = SIGILL;
504		break;
505	case T_BNDFLT+T_USER:
506		sig = SIGFPE;
507		break;
508	case T_ZERODIV+T_USER:
509		sig = SIGFPE;
510		fault_type = FPE_INTDIV;
511		break;
512	case T_OVFFLT+T_USER:
513		sig = SIGFPE;
514		fault_type = FPE_INTOVF;
515		break;
516	case T_FPEPFLT+T_USER:
517	case T_FPEIFLT+T_USER:
518		sig = SIGFPE;
519		break;
520	case T_SIGSYS+T_USER:
521		sig = SIGSYS;
522		break;
523	case T_SIGTRAP+T_USER:
524		sig = SIGTRAP;
525		fault_type = TRAP_TRACE;
526		break;
527	case T_STEPBPT+T_USER:
528		/*
529		 * This trap is used by the kernel to support single-step
530		 * debugging (although any user could generate this trap
531		 * which should probably be handled differently). When a
532		 * process is continued by a debugger with the PT_STEP
533		 * function of ptrace (single step), the kernel inserts
534		 * one or two breakpoints in the user process so that only
535		 * one instruction (or two in the case of a delayed branch)
536		 * is executed.  When this breakpoint is hit, we get the
537		 * T_STEPBPT trap.
538		 */
539		{
540			unsigned va;
541			unsigned instr;
542			struct uio uio;
543			struct iovec iov;
544			unsigned pc = PC_REGS(&frame->tf_regs);
545
546			/* read break instruction */
547			copyin((caddr_t)pc, &instr, sizeof(unsigned));
548#if 0
549			printf("trap: %s (%d) breakpoint %x at %x: (adr %x ins %x)\n",
550			       p->p_comm, p->p_pid, instr, pc,
551			       p->p_md.md_ss_addr, p->p_md.md_ss_instr); /* XXX */
552#endif
553			/* check and see if we got here by accident */
554			if ((p->p_md.md_ss_addr != pc &&
555			     p->p_md.md_ss_taken_addr != pc) ||
556			    instr != SSBREAKPOINT) {
557				sig = SIGTRAP;
558				fault_type = TRAP_TRACE;
559				break;
560			}
561			/* restore original instruction and clear BP  */
562			instr = p->p_md.md_ss_instr;
563			va = p->p_md.md_ss_addr;
564			if (va != 0) {
565				iov.iov_base = (caddr_t)&instr;
566				iov.iov_len = sizeof(int);
567				uio.uio_iov = &iov;
568				uio.uio_iovcnt = 1;
569				uio.uio_offset = (off_t)va;
570				uio.uio_resid = sizeof(int);
571				uio.uio_segflg = UIO_SYSSPACE;
572				uio.uio_rw = UIO_WRITE;
573				uio.uio_procp = curproc;
574				procfs_domem(p, p, NULL, &uio);
575			}
576
577			/* branch taken instruction */
578			instr = p->p_md.md_ss_taken_instr;
579			va = p->p_md.md_ss_taken_addr;
580			if (instr != 0) {
581				iov.iov_base = (caddr_t)&instr;
582				iov.iov_len = sizeof(int);
583				uio.uio_iov = &iov;
584				uio.uio_iovcnt = 1;
585				uio.uio_offset = (off_t)va;
586				uio.uio_resid = sizeof(int);
587				uio.uio_segflg = UIO_SYSSPACE;
588				uio.uio_rw = UIO_WRITE;
589				uio.uio_procp = curproc;
590				procfs_domem(p, p, NULL, &uio);
591			}
592#if 1
593			frame->tf_sfip = frame->tf_snip;
594			frame->tf_snip = pc | NIP_V;
595#endif
596			p->p_md.md_ss_addr = 0;
597			p->p_md.md_ss_instr = 0;
598			p->p_md.md_ss_taken_addr = 0;
599			p->p_md.md_ss_taken_instr = 0;
600			sig = SIGTRAP;
601			fault_type = TRAP_BRKPT;
602		}
603		break;
604
605	case T_USERBPT+T_USER:
606		/*
607		 * This trap is meant to be used by debuggers to implement
608		 * breakpoint debugging.  When we get this trap, we just
609		 * return a signal which gets caught by the debugger.
610		 */
611		frame->tf_sfip = frame->tf_snip;
612		frame->tf_snip = frame->tf_sxip;
613		sig = SIGTRAP;
614		fault_type = TRAP_BRKPT;
615		break;
616
617	case T_ASTFLT+T_USER:
618		uvmexp.softs++;
619		want_ast = 0;
620		if (p->p_flag & P_OWEUPC) {
621			p->p_flag &= ~P_OWEUPC;
622			ADDUPROF(p);
623		}
624		break;
625	}
626
627	/*
628	 * If trap from supervisor mode, just return
629	 */
630	if (type < T_USER)
631		return;
632
633	if (sig) {
634		sv.sival_int = fault_addr;
635		trapsignal(p, sig, fault_code, fault_type, sv);
636		/*
637		 * don't want multiple faults - we are going to
638		 * deliver signal.
639		 */
640		frame->tf_dmt0 = 0;
641		frame->tf_ipfsr = frame->tf_dpfsr = 0;
642	}
643
644	userret(p, frame, sticks);
645}
646#endif /* M88100 */
647
648#ifdef M88110
649void
650m88110_trap(unsigned type, struct trapframe *frame)
651{
652	struct proc *p;
653	u_quad_t sticks = 0;
654	struct vm_map *map;
655	vaddr_t va, pcb_onfault;
656	vm_prot_t ftype;
657	int fault_type;
658	u_long fault_code;
659	unsigned nss, fault_addr;
660	struct vmspace *vm;
661	union sigval sv;
662	int result;
663#ifdef DDB
664        int s;
665#endif
666	int sig = 0;
667	pt_entry_t *pte;
668
669	extern struct vm_map *kernel_map;
670	extern unsigned guarded_access_start;
671	extern unsigned guarded_access_end;
672	extern unsigned guarded_access_bad;
673	extern pt_entry_t *pmap_pte(pmap_t, vaddr_t);
674
675	uvmexp.traps++;
676	if ((p = curproc) == NULL)
677		p = &proc0;
678
679	if (USERMODE(frame->tf_epsr)) {
680		sticks = p->p_sticks;
681		type += T_USER;
682		p->p_md.md_tf = frame;	/* for ptrace/signals */
683	}
684	fault_type = 0;
685	fault_code = 0;
686	fault_addr = frame->tf_exip & XIP_ADDR;
687
688	switch (type) {
689	default:
690		panictrap(frame->tf_vector, frame);
691		break;
692		/*NOTREACHED*/
693
694	case T_197_READ+T_USER:
695	case T_197_READ:
696		printf("DMMU read miss: Hardware Table Searches should be enabled!\n");
697		panictrap(frame->tf_vector, frame);
698		break;
699		/*NOTREACHED*/
700	case T_197_WRITE+T_USER:
701	case T_197_WRITE:
702		printf("DMMU write miss: Hardware Table Searches should be enabled!\n");
703		panictrap(frame->tf_vector, frame);
704		break;
705		/*NOTREACHED*/
706	case T_197_INST+T_USER:
707	case T_197_INST:
708		printf("IMMU miss: Hardware Table Searches should be enabled!\n");
709		panictrap(frame->tf_vector, frame);
710		break;
711		/*NOTREACHED*/
712#ifdef DDB
713	case T_KDB_TRACE:
714		s = splhigh();
715		db_enable_interrupt();
716		ddb_break_trap(T_KDB_TRACE, (db_regs_t*)frame);
717		db_disable_interrupt();
718		splx(s);
719		return;
720	case T_KDB_BREAK:
721		s = splhigh();
722		db_enable_interrupt();
723		ddb_break_trap(T_KDB_BREAK, (db_regs_t*)frame);
724		db_disable_interrupt();
725		splx(s);
726		return;
727	case T_KDB_ENTRY:
728		s = splhigh();
729		db_enable_interrupt();
730		ddb_entry_trap(T_KDB_ENTRY, (db_regs_t*)frame);
731		db_disable_interrupt();
732		/* skip one instruction */
733		if (frame->tf_exip & 1)
734			frame->tf_exip = frame->tf_enip;
735		else
736			frame->tf_exip += 4;
737		splx(s);
738		return;
739#if 0
740	case T_ILLFLT:
741		s = splhigh();
742		db_enable_interrupt();
743		ddb_error_trap(type == T_ILLFLT ? "unimplemented opcode" :
744		       "error fault", (db_regs_t*)frame);
745		db_disable_interrupt();
746		splx(s);
747		return;
748#endif /* 0 */
749#endif /* DDB */
750	case T_ILLFLT:
751		printf("Unimplemented opcode!\n");
752		panictrap(frame->tf_vector, frame);
753		break;
754	case T_NON_MASK:
755	case T_NON_MASK+T_USER:
756		(*md.interrupt_func)(T_NON_MASK, frame);
757		return;
758	case T_INT:
759	case T_INT+T_USER:
760		(*md.interrupt_func)(T_INT, frame);
761		return;
762	case T_MISALGNFLT:
763		printf("kernel mode misaligned access exception @ 0x%08x\n",
764		    frame->tf_exip);
765		panictrap(frame->tf_vector, frame);
766		break;
767		/*NOTREACHED*/
768
769	case T_INSTFLT:
770		/* kernel mode instruction access fault.
771		 * Should never, never happen for a non-paged kernel.
772		 */
773#ifdef TRAPDEBUG
774		printf("Kernel Instruction fault exip %x isr %x ilar %x\n",
775		    frame->tf_exip, frame->tf_isr, frame->tf_ilar);
776#endif
777		panictrap(frame->tf_vector, frame);
778		break;
779		/*NOTREACHED*/
780
781	case T_DATAFLT:
782		/* kernel mode data fault */
783
784		/* data fault on the user address? */
785		if ((frame->tf_dsr & CMMU_DSR_SU) == 0) {
786			type = T_DATAFLT + T_USER;
787			goto m88110_user_fault;
788		}
789
790#ifdef TRAPDEBUG
791		printf("Kernel Data access fault exip %x dsr %x dlar %x\n",
792		    frame->tf_exip, frame->tf_dsr, frame->tf_dlar);
793#endif
794
795		fault_addr = frame->tf_dlar;
796		if (frame->tf_dsr & CMMU_DSR_RW) {
797			ftype = VM_PROT_READ;
798			fault_code = VM_PROT_READ;
799		} else {
800			ftype = VM_PROT_READ|VM_PROT_WRITE;
801			fault_code = VM_PROT_WRITE;
802		}
803
804		va = trunc_page((vaddr_t)fault_addr);
805		if (va == 0) {
806			panic("trap: bad kernel access at %x", fault_addr);
807		}
808
809		vm = p->p_vmspace;
810		map = kernel_map;
811
812		if (frame->tf_dsr & CMMU_DSR_BE) {
813			/*
814			 * If it is a guarded access, bus error is OK.
815			 */
816			if ((frame->tf_exip & XIP_ADDR) >=
817			      (unsigned)&guarded_access_start &&
818			    (frame->tf_exip & XIP_ADDR) <=
819			      (unsigned)&guarded_access_end) {
820				frame->tf_exip = (unsigned)&guarded_access_bad;
821				return;
822			}
823		}
824		if (frame->tf_dsr & (CMMU_DSR_SI | CMMU_DSR_PI)) {
825			frame->tf_dsr &= ~CMMU_DSR_WE;	/* undefined */
826			/*
827			 * On a segment or a page fault, call uvm_fault() to
828			 * resolve the fault.
829			 */
830			if ((pcb_onfault = p->p_addr->u_pcb.pcb_onfault) != 0)
831				p->p_addr->u_pcb.pcb_onfault = 0;
832			result = uvm_fault(map, va, VM_FAULT_INVALID, ftype);
833			p->p_addr->u_pcb.pcb_onfault = pcb_onfault;
834			if (result == 0)
835				return;
836		}
837		if (frame->tf_dsr & CMMU_DSR_WE) {	/* write fault  */
838			/*
839			 * This could be a write protection fault or an
840			 * exception to set the used and modified bits
841			 * in the pte. Basically, if we got a write error,
842			 * then we already have a pte entry that faulted
843			 * in from a previous seg fault or page fault.
844			 * Get the pte and check the status of the
845			 * modified and valid bits to determine if this
846			 * indeed a real write fault.  XXX smurph
847			 */
848			pte = pmap_pte(map->pmap, va);
849#ifdef DEBUG
850			if (pte == PT_ENTRY_NULL)
851				panic("NULL pte on write fault??");
852#endif
853			if (!(*pte & PG_M) && !(*pte & PG_RO)) {
854				/* Set modified bit and try the write again. */
855#ifdef TRAPDEBUG
856				printf("Corrected kernel write fault, map %x pte %x\n",
857				    map->pmap, *pte);
858#endif
859				*pte |= PG_M;
860				return;
861#if 1	/* shouldn't happen */
862			} else {
863				/* must be a real wp fault */
864#ifdef TRAPDEBUG
865				printf("Uncorrected kernel write fault, map %x pte %x\n",
866				    map->pmap, *pte);
867#endif
868				if ((pcb_onfault = p->p_addr->u_pcb.pcb_onfault) != 0)
869					p->p_addr->u_pcb.pcb_onfault = 0;
870				result = uvm_fault(map, va, VM_FAULT_INVALID, ftype);
871				p->p_addr->u_pcb.pcb_onfault = pcb_onfault;
872				if (result == 0)
873					return;
874#endif
875			}
876		}
877		panictrap(frame->tf_vector, frame);
878		/* NOTREACHED */
879	case T_INSTFLT+T_USER:
880		/* User mode instruction access fault */
881		/* FALLTHROUGH */
882	case T_DATAFLT+T_USER:
883m88110_user_fault:
884		if (type == T_INSTFLT+T_USER) {
885			ftype = VM_PROT_READ;
886			fault_code = VM_PROT_READ;
887#ifdef TRAPDEBUG
888			printf("User Instruction fault exip %x isr %x ilar %x\n",
889			    frame->tf_exip, frame->tf_isr, frame->tf_ilar);
890#endif
891		} else {
892			fault_addr = frame->tf_dlar;
893			if (frame->tf_dsr & CMMU_DSR_RW) {
894				ftype = VM_PROT_READ;
895				fault_code = VM_PROT_READ;
896			} else {
897				ftype = VM_PROT_READ|VM_PROT_WRITE;
898				fault_code = VM_PROT_WRITE;
899			}
900#ifdef TRAPDEBUG
901			printf("User Data access fault exip %x dsr %x dlar %x\n",
902			    frame->tf_exip, frame->tf_dsr, frame->tf_dlar);
903#endif
904		}
905
906		va = trunc_page((vaddr_t)fault_addr);
907
908		vm = p->p_vmspace;
909		map = &vm->vm_map;
910		if ((pcb_onfault = p->p_addr->u_pcb.pcb_onfault) != 0)
911			p->p_addr->u_pcb.pcb_onfault = 0;
912
913		/*
914		 * Call uvm_fault() to resolve non-bus error faults
915		 * whenever possible.
916		 */
917		if (type == T_DATAFLT+T_USER) {
918			/* data faults */
919			if (frame->tf_dsr & CMMU_DSR_BE) {
920				/* bus error */
921				result = EACCES;
922			} else
923			if (frame->tf_dsr & (CMMU_DSR_SI | CMMU_DSR_PI)) {
924				/* segment or page fault */
925				result = uvm_fault(map, va, VM_FAULT_INVALID, ftype);
926				p->p_addr->u_pcb.pcb_onfault = pcb_onfault;
927				if (result == EACCES)
928					result = EFAULT;
929			} else
930			if (frame->tf_dsr & (CMMU_DSR_CP | CMMU_DSR_WA)) {
931				/* copyback or write allocate error */
932				result = EACCES;
933			} else
934			if (frame->tf_dsr & CMMU_DSR_WE) {
935				/* write fault  */
936				/* This could be a write protection fault or an
937				 * exception to set the used and modified bits
938				 * in the pte. Basically, if we got a write
939				 * error, then we already have a pte entry that
940				 * faulted in from a previous seg fault or page
941				 * fault.
942				 * Get the pte and check the status of the
943				 * modified and valid bits to determine if this
944				 * indeed a real write fault.  XXX smurph
945				 */
946				pte = pmap_pte(vm_map_pmap(map), va);
947#ifdef DEBUG
948				if (pte == PT_ENTRY_NULL)
949					panic("NULL pte on write fault??");
950#endif
951				if (!(*pte & PG_M) && !(*pte & PG_RO)) {
952					/*
953					 * Set modified bit and try the
954					 * write again.
955					 */
956#ifdef TRAPDEBUG
957					printf("Corrected userland write fault, map %x pte %x\n",
958					    map->pmap, *pte);
959#endif
960					*pte |= PG_M;
961					/*
962					 * invalidate ATCs to force
963					 * table search
964					 */
965					set_dcmd(CMMU_DCMD_INV_UATC);
966					return;
967				} else {
968					/* must be a real wp fault */
969#ifdef TRAPDEBUG
970					printf("Uncorrected userland write fault, map %x pte %x\n",
971					    map->pmap, *pte);
972#endif
973					result = uvm_fault(map, va, VM_FAULT_INVALID, ftype);
974					p->p_addr->u_pcb.pcb_onfault = pcb_onfault;
975					if (result == EACCES)
976						result = EFAULT;
977				}
978			} else {
979#ifdef TRAPDEBUG
980				printf("Unexpected Data access fault dsr %x\n",
981				    frame->tf_dsr);
982#endif
983				panictrap(frame->tf_vector, frame);
984			}
985		} else {
986			/* instruction faults */
987			if (frame->tf_isr &
988			    (CMMU_ISR_BE | CMMU_ISR_SP | CMMU_ISR_TBE)) {
989				/* bus error, supervisor protection */
990				result = EACCES;
991			} else
992			if (frame->tf_isr & (CMMU_ISR_SI | CMMU_ISR_PI)) {
993				/* segment or page fault */
994				result = uvm_fault(map, va, VM_FAULT_INVALID, ftype);
995				p->p_addr->u_pcb.pcb_onfault = pcb_onfault;
996				if (result == EACCES)
997					result = EFAULT;
998			} else {
999#ifdef TRAPDEBUG
1000				printf("Unexpected Instruction fault isr %x\n",
1001				    frame->tf_isr);
1002#endif
1003				panictrap(frame->tf_vector, frame);
1004			}
1005		}
1006
1007		if ((caddr_t)va >= vm->vm_maxsaddr) {
1008			if (result == 0) {
1009				nss = btoc(USRSTACK - va);/* XXX check this */
1010				if (nss > vm->vm_ssize)
1011					vm->vm_ssize = nss;
1012			}
1013		}
1014
1015		/*
1016		 * This could be a fault caused in copyin*()
1017		 * while accessing user space.
1018		 */
1019		if (result != 0 && pcb_onfault != 0) {
1020			frame->tf_exip = pcb_onfault;
1021			/*
1022			 * Continue as if the fault had been resolved.
1023			 */
1024			result = 0;
1025		}
1026
1027		if (result != 0) {
1028			sig = result == EACCES ? SIGBUS : SIGSEGV;
1029			fault_type = result == EACCES ?
1030			    BUS_ADRERR : SEGV_MAPERR;
1031		}
1032		break;
1033	case T_MISALGNFLT+T_USER:
1034		/* Fix any misaligned ld.d or st.d instructions */
1035		sig = double_reg_fixup(frame);
1036		fault_type = BUS_ADRALN;
1037		break;
1038	case T_PRIVINFLT+T_USER:
1039	case T_ILLFLT+T_USER:
1040#ifndef DDB
1041	case T_KDB_BREAK:
1042	case T_KDB_ENTRY:
1043	case T_KDB_TRACE:
1044#endif
1045	case T_KDB_BREAK+T_USER:
1046	case T_KDB_ENTRY+T_USER:
1047	case T_KDB_TRACE+T_USER:
1048		sig = SIGILL;
1049		break;
1050	case T_BNDFLT+T_USER:
1051		sig = SIGFPE;
1052		break;
1053	case T_ZERODIV+T_USER:
1054		sig = SIGFPE;
1055		fault_type = FPE_INTDIV;
1056		break;
1057	case T_OVFFLT+T_USER:
1058		sig = SIGFPE;
1059		fault_type = FPE_INTOVF;
1060		break;
1061	case T_FPEPFLT+T_USER:
1062	case T_FPEIFLT+T_USER:
1063		sig = SIGFPE;
1064		break;
1065	case T_SIGSYS+T_USER:
1066		sig = SIGSYS;
1067		break;
1068	case T_SIGTRAP+T_USER:
1069		sig = SIGTRAP;
1070		fault_type = TRAP_TRACE;
1071		break;
1072	case T_STEPBPT+T_USER:
1073		/*
1074		 * This trap is used by the kernel to support single-step
1075		 * debugging (although any user could generate this trap
1076		 * which should probably be handled differently). When a
1077		 * process is continued by a debugger with the PT_STEP
1078		 * function of ptrace (single step), the kernel inserts
1079		 * one or two breakpoints in the user process so that only
1080		 * one instruction (or two in the case of a delayed branch)
1081		 * is executed.  When this breakpoint is hit, we get the
1082		 * T_STEPBPT trap.
1083		 */
1084		{
1085			unsigned instr;
1086			struct uio uio;
1087			struct iovec iov;
1088			unsigned pc = PC_REGS(&frame->tf_regs);
1089
1090			/* read break instruction */
1091			copyin((caddr_t)pc, &instr, sizeof(unsigned));
1092#if 0
1093			printf("trap: %s (%d) breakpoint %x at %x: (adr %x ins %x)\n",
1094			       p->p_comm, p->p_pid, instr, pc,
1095			       p->p_md.md_ss_addr, p->p_md.md_ss_instr); /* XXX */
1096#endif
1097			/* check and see if we got here by accident */
1098#ifdef notyet
1099			if (p->p_md.md_ss_addr != pc || instr != SSBREAKPOINT) {
1100				sig = SIGTRAP;
1101				fault_type = TRAP_TRACE;
1102				break;
1103			}
1104#endif
1105			/* restore original instruction and clear BP  */
1106			/*sig = suiword((caddr_t)pc, p->p_md.md_ss_instr);*/
1107			instr = p->p_md.md_ss_instr;
1108			if (instr != 0) {
1109				iov.iov_base = (caddr_t)&instr;
1110				iov.iov_len = sizeof(int);
1111				uio.uio_iov = &iov;
1112				uio.uio_iovcnt = 1;
1113				uio.uio_offset = (off_t)pc;
1114				uio.uio_resid = sizeof(int);
1115				uio.uio_segflg = UIO_SYSSPACE;
1116				uio.uio_rw = UIO_WRITE;
1117				uio.uio_procp = curproc;
1118			}
1119
1120			p->p_md.md_ss_addr = 0;
1121			sig = SIGTRAP;
1122			fault_type = TRAP_BRKPT;
1123			break;
1124		}
1125	case T_USERBPT+T_USER:
1126		/*
1127		 * This trap is meant to be used by debuggers to implement
1128		 * breakpoint debugging.  When we get this trap, we just
1129		 * return a signal which gets caught by the debugger.
1130		 */
1131		sig = SIGTRAP;
1132		fault_type = TRAP_BRKPT;
1133		break;
1134
1135	case T_ASTFLT+T_USER:
1136		uvmexp.softs++;
1137		want_ast = 0;
1138		if (p->p_flag & P_OWEUPC) {
1139			p->p_flag &= ~P_OWEUPC;
1140			ADDUPROF(p);
1141		}
1142		break;
1143	}
1144
1145	/*
1146	 * If trap from supervisor mode, just return
1147	 */
1148	if (type < T_USER)
1149		return;
1150
1151	if (sig) {
1152		sv.sival_int = fault_addr;
1153		trapsignal(p, sig, fault_code, fault_type, sv);
1154	}
1155
1156	userret(p, frame, sticks);
1157}
1158#endif /* M88110 */
1159
1160__dead void
1161error_fatal(struct trapframe *frame)
1162{
1163	if (frame->tf_vector == 0)
1164		printf("\nReset Exception\n");
1165	else
1166		printf("\nError Exception\n");
1167
1168#ifdef DDB
1169	regdump((struct trapframe*)frame);
1170#endif
1171	panic("unrecoverable exception %d", frame->tf_vector);
1172}
1173
1174#ifdef M88100
1175void
1176m88100_syscall(register_t code, struct trapframe *tf)
1177{
1178	int i, nsys, nap;
1179	struct sysent *callp;
1180	struct proc *p;
1181	int error;
1182	register_t args[11], rval[2], *ap;
1183	u_quad_t sticks;
1184#ifdef DIAGNOSTIC
1185	extern struct pcb *curpcb;
1186#endif
1187
1188	uvmexp.syscalls++;
1189
1190	p = curproc;
1191
1192	callp = p->p_emul->e_sysent;
1193	nsys  = p->p_emul->e_nsysent;
1194
1195#ifdef DIAGNOSTIC
1196	if (USERMODE(tf->tf_epsr) == 0)
1197		panic("syscall");
1198	if (curpcb != &p->p_addr->u_pcb)
1199		panic("syscall curpcb/ppcb");
1200	if (tf != (struct trapframe *)&curpcb->user_state)
1201		panic("syscall trapframe");
1202#endif
1203
1204	sticks = p->p_sticks;
1205	p->p_md.md_tf = tf;
1206
1207	/*
1208	 * For 88k, all the arguments are passed in the registers (r2-r12)
1209	 * For syscall (and __syscall), r2 (and r3) has the actual code.
1210	 * __syscall  takes a quad syscall number, so that other
1211	 * arguments are at their natural alignments.
1212	 */
1213	ap = &tf->tf_r[2];
1214	nap = 11; /* r2-r12 */
1215
1216	switch (code) {
1217	case SYS_syscall:
1218		code = *ap++;
1219		nap--;
1220		break;
1221	case SYS___syscall:
1222		if (callp != sysent)
1223			break;
1224		code = ap[_QUAD_LOWWORD];
1225		ap += 2;
1226		nap -= 2;
1227		break;
1228	}
1229
1230	/* Callp currently points to syscall, which returns ENOSYS. */
1231	if (code < 0 || code >= nsys)
1232		callp += p->p_emul->e_nosys;
1233	else {
1234		callp += code;
1235		i = callp->sy_argsize / sizeof(register_t);
1236		if (i > nap)
1237			panic("syscall nargs");
1238		/*
1239		 * just copy them; syscall stub made sure all the
1240		 * args are moved from user stack to registers.
1241		 */
1242		bcopy((caddr_t)ap, (caddr_t)args, i * sizeof(register_t));
1243	}
1244
1245#ifdef SYSCALL_DEBUG
1246	scdebug_call(p, code, args);
1247#endif
1248#ifdef KTRACE
1249	if (KTRPOINT(p, KTR_SYSCALL))
1250		ktrsyscall(p, code, callp->sy_argsize, args);
1251#endif
1252	rval[0] = 0;
1253	rval[1] = tf->tf_r[3];
1254#if NSYSTRACE > 0
1255	if (ISSET(p->p_flag, P_SYSTRACE))
1256		error = systrace_redirect(code, p, args, rval);
1257	else
1258#endif
1259		error = (*callp->sy_call)(p, args, rval);
1260	/*
1261	 * system call will look like:
1262	 *	 ld r10, r31, 32; r10,r11,r12 might be garbage.
1263	 *	 ld r11, r31, 36
1264	 *	 ld r12, r31, 40
1265	 *	 or r13, r0, <code>
1266	 *       tb0 0, r0, <128> <- sxip
1267	 *	 br err 	  <- snip
1268	 *       jmp r1 	  <- sfip
1269	 *  err: or.u r3, r0, hi16(errno)
1270	 *	 st r2, r3, lo16(errno)
1271	 *	 subu r2, r0, 1
1272	 *	 jmp r1
1273	 *
1274	 * So, when we take syscall trap, sxip/snip/sfip will be as
1275	 * shown above.
1276	 * Given this,
1277	 * 1. If the system call returned 0, need to skip nip.
1278	 *	nip = fip, fip += 4
1279	 *    (doesn't matter what fip + 4 will be but we will never
1280	 *    execute this since jmp r1 at nip will change the execution flow.)
1281	 * 2. If the system call returned an errno > 0, plug the value
1282	 *    in r2, and leave nip and fip unchanged. This will have us
1283	 *    executing "br err" on return to user space.
1284	 * 3. If the system call code returned ERESTART,
1285	 *    we need to rexecute the trap instruction. Back up the pipe
1286	 *    line.
1287	 *     fip = nip, nip = xip
1288	 * 4. If the system call returned EJUSTRETURN, don't need to adjust
1289	 *    any pointers.
1290	 */
1291
1292	switch (error) {
1293	case 0:
1294		/*
1295		 * If fork succeeded and we are the child, our stack
1296		 * has moved and the pointer tf is no longer valid,
1297		 * and p is wrong.  Compute the new trapframe pointer.
1298		 * (The trap frame invariably resides at the
1299		 * tippity-top of the u. area.)
1300		 */
1301		p = curproc;
1302		tf = (struct trapframe *)USER_REGS(p);
1303		tf->tf_r[2] = rval[0];
1304		tf->tf_r[3] = rval[1];
1305		tf->tf_epsr &= ~PSR_C;
1306		tf->tf_snip = tf->tf_sfip & ~NIP_E;
1307		tf->tf_sfip = tf->tf_snip + 4;
1308		break;
1309	case ERESTART:
1310		/*
1311		 * If (error == ERESTART), back up the pipe line. This
1312		 * will end up reexecuting the trap.
1313		 */
1314		tf->tf_epsr &= ~PSR_C;
1315		tf->tf_sfip = tf->tf_snip & ~FIP_E;
1316		tf->tf_snip = tf->tf_sxip & ~NIP_E;
1317		break;
1318	case EJUSTRETURN:
1319		/* if (error == EJUSTRETURN), leave the ip's alone */
1320		tf->tf_epsr &= ~PSR_C;
1321		break;
1322	default:
1323		/* error != ERESTART && error != EJUSTRETURN*/
1324		if (p->p_emul->e_errno)
1325			error = p->p_emul->e_errno[error];
1326		tf->tf_r[2] = error;
1327		tf->tf_epsr |= PSR_C;   /* fail */
1328		tf->tf_snip = tf->tf_snip & ~NIP_E;
1329		tf->tf_sfip = tf->tf_sfip & ~FIP_E;
1330		break;
1331	}
1332#ifdef SYSCALL_DEBUG
1333	scdebug_ret(p, code, error, rval);
1334#endif
1335	userret(p, tf, sticks);
1336#ifdef KTRACE
1337	if (KTRPOINT(p, KTR_SYSRET))
1338		ktrsysret(p, code, error, rval[0]);
1339#endif
1340}
1341#endif /* M88100 */
1342
1343#ifdef M88110
1344/* Instruction pointers operate differently on mc88110 */
1345void
1346m88110_syscall(register_t code, struct trapframe *tf)
1347{
1348	int i, nsys, nap;
1349	struct sysent *callp;
1350	struct proc *p;
1351	int error;
1352	register_t args[11], rval[2], *ap;
1353	u_quad_t sticks;
1354#ifdef DIAGNOSTIC
1355	extern struct pcb *curpcb;
1356#endif
1357
1358	uvmexp.syscalls++;
1359
1360	p = curproc;
1361
1362	callp = p->p_emul->e_sysent;
1363	nsys  = p->p_emul->e_nsysent;
1364
1365#ifdef DIAGNOSTIC
1366	if (USERMODE(tf->tf_epsr) == 0)
1367		panic("syscall");
1368	if (curpcb != &p->p_addr->u_pcb)
1369		panic("syscall curpcb/ppcb");
1370	if (tf != (struct trapframe *)&curpcb->user_state)
1371		panic("syscall trapframe");
1372#endif
1373
1374	sticks = p->p_sticks;
1375	p->p_md.md_tf = tf;
1376
1377	/*
1378	 * For 88k, all the arguments are passed in the registers (r2-r12)
1379	 * For syscall (and __syscall), r2 (and r3) has the actual code.
1380	 * __syscall  takes a quad syscall number, so that other
1381	 * arguments are at their natural alignments.
1382	 */
1383	ap = &tf->tf_r[2];
1384	nap = 11;	/* r2-r12 */
1385
1386	switch (code) {
1387	case SYS_syscall:
1388		code = *ap++;
1389		nap--;
1390		break;
1391	case SYS___syscall:
1392		if (callp != sysent)
1393			break;
1394		code = ap[_QUAD_LOWWORD];
1395		ap += 2;
1396		nap -= 2;
1397		break;
1398	}
1399
1400	/* Callp currently points to syscall, which returns ENOSYS. */
1401	if (code < 0 || code >= nsys)
1402		callp += p->p_emul->e_nosys;
1403	else {
1404		callp += code;
1405		i = callp->sy_argsize / sizeof(register_t);
1406		if (i > nap)
1407			panic("syscall nargs");
1408		/*
1409		 * just copy them; syscall stub made sure all the
1410		 * args are moved from user stack to registers.
1411		 */
1412		bcopy((caddr_t)ap, (caddr_t)args, i * sizeof(register_t));
1413	}
1414#ifdef SYSCALL_DEBUG
1415	scdebug_call(p, code, args);
1416#endif
1417#ifdef KTRACE
1418	if (KTRPOINT(p, KTR_SYSCALL))
1419		ktrsyscall(p, code, callp->sy_argsize, args);
1420#endif
1421	rval[0] = 0;
1422	rval[1] = tf->tf_r[3];
1423#if NSYSTRACE > 0
1424	if (ISSET(p->p_flag, P_SYSTRACE))
1425		error = systrace_redirect(code, p, args, rval);
1426	else
1427#endif
1428		error = (*callp->sy_call)(p, args, rval);
1429	/*
1430	 * system call will look like:
1431	 *	 ld r10, r31, 32; r10,r11,r12 might be garbage.
1432	 *	 ld r11, r31, 36
1433	 *	 ld r12, r31, 40
1434	 *	 or r13, r0, <code>
1435	 *       tb0 0, r0, <128> <- exip
1436	 *	 br err 	  <- enip
1437	 *       jmp r1
1438	 *  err: or.u r3, r0, hi16(errno)
1439	 *	 st r2, r3, lo16(errno)
1440	 *	 subu r2, r0, 1
1441	 *	 jmp r1
1442	 *
1443	 * So, when we take syscall trap, exip/enip will be as
1444	 * shown above.
1445	 * Given this,
1446	 * 1. If the system call returned 0, need to jmp r1.
1447	 *    exip += 8
1448	 * 2. If the system call returned an errno > 0, increment
1449	 *    exip += 4 and plug the value in r2. This will have us
1450	 *    executing "br err" on return to user space.
1451	 * 3. If the system call code returned ERESTART,
1452	 *    we need to rexecute the trap instruction. leave exip as is.
1453	 * 4. If the system call returned EJUSTRETURN, just return.
1454	 *    exip += 4
1455	 */
1456
1457	switch (error) {
1458	case 0:
1459		/*
1460		 * If fork succeeded and we are the child, our stack
1461		 * has moved and the pointer tf is no longer valid,
1462		 * and p is wrong.  Compute the new trapframe pointer.
1463		 * (The trap frame invariably resides at the
1464		 * tippity-top of the u. area.)
1465		 */
1466		p = curproc;
1467		tf = (struct trapframe *)USER_REGS(p);
1468		tf->tf_r[2] = rval[0];
1469		tf->tf_r[3] = rval[1];
1470		tf->tf_epsr &= ~PSR_C;
1471		/* skip two instructions */
1472		if (tf->tf_exip & 1)
1473			tf->tf_exip = tf->tf_enip + 4;
1474		else
1475			tf->tf_exip += 4 + 4;
1476		break;
1477	case ERESTART:
1478		/*
1479		 * Reexecute the trap.
1480		 * exip is already at the trap instruction, so
1481		 * there is nothing to do.
1482		 */
1483		tf->tf_epsr &= ~PSR_C;
1484		break;
1485	case EJUSTRETURN:
1486		tf->tf_epsr &= ~PSR_C;
1487		/* skip one instruction */
1488		if (tf->tf_exip & 1)
1489			tf->tf_exip = tf->tf_enip;
1490		else
1491			tf->tf_exip += 4;
1492		break;
1493	default:
1494		if (p->p_emul->e_errno)
1495			error = p->p_emul->e_errno[error];
1496		tf->tf_r[2] = error;
1497		tf->tf_epsr |= PSR_C;   /* fail */
1498		/* skip one instruction */
1499		if (tf->tf_exip & 1)
1500			tf->tf_exip = tf->tf_enip;
1501		else
1502			tf->tf_exip += 4;
1503		break;
1504	}
1505
1506#ifdef SYSCALL_DEBUG
1507	scdebug_ret(p, code, error, rval);
1508#endif
1509	userret(p, tf, sticks);
1510#ifdef KTRACE
1511	if (KTRPOINT(p, KTR_SYSRET))
1512		ktrsysret(p, code, error, rval[0]);
1513#endif
1514}
1515#endif	/* M88110 */
1516
1517/*
1518 * Set up return-value registers as fork() libc stub expects,
1519 * and do normal return-to-user-mode stuff.
1520 */
1521void
1522child_return(arg)
1523	void *arg;
1524{
1525	struct proc *p = arg;
1526	struct trapframe *tf;
1527
1528	tf = (struct trapframe *)USER_REGS(p);
1529	tf->tf_r[2] = 0;
1530	tf->tf_r[3] = 0;
1531	tf->tf_epsr &= ~PSR_C;
1532	if (cputyp != CPU_88110) {
1533		tf->tf_snip = tf->tf_sfip & XIP_ADDR;
1534		tf->tf_sfip = tf->tf_snip + 4;
1535	} else {
1536		/* skip two instructions */
1537		if (tf->tf_exip & 1)
1538			tf->tf_exip = tf->tf_enip + 4;
1539		else
1540			tf->tf_exip += 4 + 4;
1541	}
1542
1543	userret(p, tf, p->p_sticks);
1544#ifdef KTRACE
1545	if (KTRPOINT(p, KTR_SYSRET))
1546		ktrsysret(p, SYS_fork, 0, 0);
1547#endif
1548}
1549
1550#ifdef PTRACE
1551
1552/*
1553 * User Single Step Debugging Support
1554 */
1555
1556#include <sys/ptrace.h>
1557
1558unsigned ss_get_value(struct proc *, unsigned, int);
1559int ss_put_value(struct proc *, unsigned, unsigned, int);
1560unsigned ss_branch_taken(unsigned, unsigned,
1561    unsigned (*func)(unsigned int, struct reg *), struct reg *);
1562unsigned int ss_getreg_val(unsigned int, struct reg *);
1563int ss_inst_branch(unsigned);
1564int ss_inst_delayed(unsigned);
1565unsigned ss_next_instr_address(struct proc *, unsigned, unsigned);
1566
1567unsigned
1568ss_get_value(struct proc *p, unsigned addr, int size)
1569{
1570	struct uio uio;
1571	struct iovec iov;
1572	unsigned value;
1573
1574	iov.iov_base = (caddr_t)&value;
1575	iov.iov_len = size;
1576	uio.uio_iov = &iov;
1577	uio.uio_iovcnt = 1;
1578	uio.uio_offset = (off_t)addr;
1579	uio.uio_resid = size;
1580	uio.uio_segflg = UIO_SYSSPACE;
1581	uio.uio_rw = UIO_READ;
1582	uio.uio_procp = curproc;
1583	procfs_domem(curproc, p, NULL, &uio);
1584	return value;
1585}
1586
1587int
1588ss_put_value(struct proc *p, unsigned addr, unsigned value, int size)
1589{
1590	struct uio uio;
1591	struct iovec iov;
1592
1593	iov.iov_base = (caddr_t)&value;
1594	iov.iov_len = size;
1595	uio.uio_iov = &iov;
1596	uio.uio_iovcnt = 1;
1597	uio.uio_offset = (off_t)addr;
1598	uio.uio_resid = size;
1599	uio.uio_segflg = UIO_SYSSPACE;
1600	uio.uio_rw = UIO_WRITE;
1601	uio.uio_procp = curproc;
1602	return procfs_domem(curproc, p, NULL, &uio);
1603}
1604
1605/*
1606 * ss_branch_taken(instruction, program counter, func, func_data)
1607 *
1608 * instruction will be a control flow instruction location at address pc.
1609 * Branch taken is supposed to return the address to which the instruction
1610 * would jump if the branch is taken. Func can be used to get the current
1611 * register values when invoked with a register number and func_data as
1612 * arguments.
1613 *
1614 * If the instruction is not a control flow instruction, panic.
1615 */
1616unsigned
1617ss_branch_taken(unsigned inst, unsigned pc,
1618    unsigned (*func)(unsigned int, struct reg *), struct reg *func_data)
1619{
1620	/* check if br/bsr */
1621	if ((inst & 0xf0000000) == 0xc0000000) {
1622		/* signed 26 bit pc relative displacement, shift left two bits */
1623		inst = (inst & 0x03ffffff) << 2;
1624		/* check if sign extension is needed */
1625		if (inst & 0x08000000)
1626			inst |= 0xf0000000;
1627		return (pc + inst);
1628	}
1629
1630	/* check if bb0/bb1/bcnd case */
1631	switch (inst & 0xf8000000) {
1632	case 0xd0000000: /* bb0 */
1633	case 0xd8000000: /* bb1 */
1634	case 0xe8000000: /* bcnd */
1635		/* signed 16 bit pc relative displacement, shift left two bits */
1636		inst = (inst & 0x0000ffff) << 2;
1637		/* check if sign extension is needed */
1638		if (inst & 0x00020000)
1639			inst |= 0xfffc0000;
1640		return (pc + inst);
1641	}
1642
1643	/* check jmp/jsr case */
1644	/* check bits 5-31, skipping 10 & 11 */
1645	if ((inst & 0xfffff3e0) == 0xf400c000)
1646		return (*func)(inst & 0x1f, func_data);	 /* the register value */
1647
1648	/* can't happen */
1649	return (0);
1650}
1651
1652/*
1653 * ss_getreg_val - handed a register number and an exception frame.
1654 *              Returns the value of the register in the specified
1655 *              frame. Only makes sense for general registers.
1656 */
1657unsigned int
1658ss_getreg_val(unsigned int regno, struct reg *regs)
1659{
1660	return (regno == 0 ? 0 : regs->r[regno]);
1661}
1662
1663int
1664ss_inst_branch(unsigned ins)
1665{
1666	/* check high five bits */
1667
1668	switch (ins >> (32 - 5)) {
1669	case 0x18: /* br */
1670	case 0x1a: /* bb0 */
1671	case 0x1b: /* bb1 */
1672	case 0x1d: /* bcnd */
1673		return TRUE;
1674		break;
1675	case 0x1e: /* could be jmp */
1676		if ((ins & 0xfffffbe0) == 0xf400c000)
1677			return TRUE;
1678	}
1679
1680	return FALSE;
1681}
1682
1683/* ss_inst_delayed - this instruction is followed by a delay slot. Could be
1684   br.n, bsr.n bb0.n, bb1.n, bcnd.n or jmp.n or jsr.n */
1685
1686int
1687ss_inst_delayed(unsigned ins)
1688{
1689	/* check the br, bsr, bb0, bb1, bcnd cases */
1690	switch ((ins & 0xfc000000) >> (32 - 6)) {
1691	case 0x31: /* br */
1692	case 0x33: /* bsr */
1693	case 0x35: /* bb0 */
1694	case 0x37: /* bb1 */
1695	case 0x3b: /* bcnd */
1696		return TRUE;
1697	}
1698
1699	/* check the jmp, jsr cases */
1700	/* mask out bits 0-4, bit 11 */
1701	return ((ins & 0xfffff7e0) == 0xf400c400) ? TRUE : FALSE;
1702}
1703
1704unsigned
1705ss_next_instr_address(struct proc *p, unsigned pc, unsigned delay_slot)
1706{
1707	if (delay_slot == 0)
1708		return (pc + 4);
1709	else {
1710		if (ss_inst_delayed(ss_get_value(p, pc, sizeof(int))))
1711			return (pc + 4);
1712		else
1713			return pc;
1714	}
1715}
1716
1717int
1718cpu_singlestep(p)
1719	struct proc *p;
1720{
1721	struct reg *sstf = USER_REGS(p);
1722	unsigned pc, brpc;
1723	int bpinstr = SSBREAKPOINT;
1724	unsigned curinstr;
1725
1726	pc = PC_REGS(sstf);
1727	/*
1728	 * User was stopped at pc, e.g. the instruction
1729	 * at pc was not executed.
1730	 * Fetch what's at the current location.
1731	 */
1732	curinstr = ss_get_value(p, pc, sizeof(int));
1733
1734	/* compute next address after current location */
1735	if (curinstr != 0) {
1736		if (ss_inst_branch(curinstr) ||
1737		    inst_call(curinstr) || inst_return(curinstr)) {
1738			brpc = ss_branch_taken(curinstr, pc, ss_getreg_val, sstf);
1739			if (brpc != pc) {   /* self-branches are hopeless */
1740				p->p_md.md_ss_taken_addr = brpc;
1741				p->p_md.md_ss_taken_instr =
1742				    ss_get_value(p, brpc, sizeof(int));
1743				/* Store breakpoint instruction at the
1744				   "next" location now. */
1745				if (ss_put_value(p, brpc, bpinstr,
1746				    sizeof(int)) != 0)
1747					return (EFAULT);
1748			}
1749		}
1750		pc = ss_next_instr_address(p, pc, 0);
1751	} else {
1752		pc = PC_REGS(sstf) + 4;
1753	}
1754
1755	if (p->p_md.md_ss_addr != NULL) {
1756		return (EFAULT);
1757	}
1758
1759	p->p_md.md_ss_addr = pc;
1760
1761	/* Fetch what's at the "next" location. */
1762	p->p_md.md_ss_instr = ss_get_value(p, pc, sizeof(int));
1763
1764	/* Store breakpoint instruction at the "next" location now. */
1765	if (ss_put_value(p, pc, bpinstr, sizeof(int)) != 0)
1766		return (EFAULT);
1767
1768	return (0);
1769}
1770
1771#endif	/* PTRACE */
1772
1773#ifdef DIAGNOSTIC
1774void
1775splassert_check(int wantipl, const char *func)
1776{
1777	int oldipl;
1778
1779	/*
1780	 * This will raise the spl if too low,
1781	 * in a feeble attempt to reduce further damage.
1782	 */
1783	oldipl = raiseipl(wantipl);
1784
1785	if (oldipl < wantipl) {
1786		splassert_fail(wantipl, oldipl, func);
1787	}
1788}
1789#endif
1790
1791/*
1792 * ld.d and st.d instructions referencing long aligned but not long long
1793 * aligned addresses will trigger a misaligned address exception.
1794 *
1795 * This routine attempts to recover these (valid) statements, by simulating
1796 * the splitted form of the instruction. If it fails, it returns the
1797 * appropriate signal number to deliver.
1798 */
1799int
1800double_reg_fixup(struct trapframe *frame)
1801{
1802	u_int32_t pc, instr, value;
1803	int regno, store;
1804	vaddr_t addr;
1805
1806	/*
1807	 * Decode the faulting instruction.
1808	 */
1809
1810	pc = PC_REGS(&frame->tf_regs);
1811	if (copyin((void *)pc, &instr, sizeof(u_int32_t)) != 0)
1812		return SIGSEGV;
1813
1814	switch (instr & 0xfc00ff00) {
1815	case 0xf4001000:	/* ld.d rD, rS1, rS2 */
1816		addr = frame->tf_r[(instr >> 16) & 0x1f]
1817		    + frame->tf_r[(instr & 0x1f)];
1818		store = 0;
1819		break;
1820	case 0xf4001200:	/* ld.d rD, rS1[rS2] */
1821		addr = frame->tf_r[(instr >> 16) & 0x1f]
1822		    + (frame->tf_r[(instr & 0x1f)] << 3);
1823		store = 0;
1824		break;
1825	case 0xf4002000:	/* st.d rD, rS1, rS2 */
1826		addr = frame->tf_r[(instr >> 16) & 0x1f]
1827		    + frame->tf_r[(instr & 0x1f)];
1828		store = 1;
1829		break;
1830	case 0xf4002200:	/* st.d rD, rS1[rS2] */
1831		addr = frame->tf_r[(instr >> 16) & 0x1f]
1832		    + (frame->tf_r[(instr & 0x1f)] << 3);
1833		store = 1;
1834		break;
1835	default:
1836		switch (instr & 0xfc000000) {
1837		case 0x10000000:	/* ld.d rD, rS, imm16 */
1838			addr = (instr & 0x0000ffff) +
1839			    frame->tf_r[(instr >> 16) & 0x1f];
1840			store = 0;
1841			break;
1842		case 0x20000000:	/* st.d rD, rS, imm16 */
1843			addr = (instr & 0x0000ffff) +
1844			    frame->tf_r[(instr >> 16) & 0x1f];
1845			store = 1;
1846			break;
1847		default:
1848			return SIGBUS;
1849		}
1850		break;
1851	}
1852
1853	/* We only handle long but not long long aligned access here */
1854	if ((addr & 0x07) != 4)
1855		return SIGBUS;
1856
1857	regno = (instr >> 21) & 0x1f;
1858
1859	if (store) {
1860		/*
1861		 * Two word stores.
1862		 */
1863		value = frame->tf_r[regno++];
1864		if (copyout(&value, (void *)addr, sizeof(u_int32_t)) != 0)
1865			return SIGSEGV;
1866		if (regno == 32)
1867			value = 0;
1868		else
1869			value = frame->tf_r[regno];
1870		if (copyout(&value, (void *)(addr + 4), sizeof(u_int32_t)) != 0)
1871			return SIGSEGV;
1872	} else {
1873		/*
1874		 * Two word loads. r0 should be left unaltered, but the
1875		 * value should still be fetched even if it is discarded.
1876		 */
1877		if (copyin((void *)addr, &value, sizeof(u_int32_t)) != 0)
1878			return SIGSEGV;
1879		if (regno != 0)
1880			frame->tf_r[regno] = value;
1881		if (copyin((void *)(addr + 4), &value, sizeof(u_int32_t)) != 0)
1882			return SIGSEGV;
1883		if (regno != 31)
1884			frame->tf_r[regno + 1] = value;
1885	}
1886
1887	return 0;
1888}
1889