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