xref: /original-bsd/sys/vax/vax/locore.s (revision 23a40993)
1/*	locore.s	4.83	83/06/19	*/
2
3#include "../machine/psl.h"
4#include "../machine/pte.h"
5
6#include "../h/errno.h"
7
8#include "../vax/mtpr.h"
9#include "../vax/trap.h"
10#include "../vax/cpu.h"
11#include "../vax/nexus.h"
12#include "../vax/cons.h"
13#include "../vax/clock.h"
14#include "../vaxuba/ubareg.h"
15
16#include "dh.h"
17#include "dz.h"
18#include "uu.h"
19#include "mba.h"
20
21	.set	HIGH,0x1f	# mask for total disable
22	.set	MCKVEC,4	# offset into scb of machine check vector
23	.set	NBPG,512
24	.set	PGSHIFT,9
25
26	.set	NISP,3		# number of interrupt stack pages
27
28/*
29 * User structure is UPAGES at top of user space.
30 */
31	.globl	_u
32	.set	_u,0x80000000 - UPAGES*NBPG
33
34/*
35 * Restart parameter block
36 * This is filled in in machdep.c in startup().
37 * It MUST be page aligned.
38 * When auto-restart occurs, we run restart() in machdep.c, which
39 * takes a core-dump and then cold-starts.
40 */
41	.globl	_rpb
42_rpb:
43	.space	508
44erpb:
45	.space	4
46	.globl	_intstack
47_intstack:
48	.space	NISP*NBPG
49eintstack:
50
51/*
52 * Do a dump.
53 * Called by auto-restart.
54 * May be called manually.
55 */
56	.align	2
57	.globl	_doadump
58_doadump:
59	nop; nop				# .word 0x0101
60#define	_rpbmap	_Sysmap+8			# scb, UNIvec, rpb, istack*4
61	bicl2	$PG_PROT,_rpbmap
62	bisl2	$PG_KW,_rpbmap
63	tstl	_rpb+RP_FLAG			# dump only once!
64	bneq	1f
65	incl	_rpb+RP_FLAG
66	mtpr	$0,$TBIA
67	movl	sp,erpb
68	movab	erpb,sp
69	mfpr	$PCBB,-(sp)
70	mfpr	$MAPEN,-(sp)
71	mfpr	$IPL,-(sp)
72	mtpr	$0,$MAPEN
73	mtpr	$HIGH,$IPL
74	pushr	$0x3fff
75	calls	$0,_dumpsys
761:
77	mfpr	$TXCS,r0
78	bitl	$TXCS_RDY,r0
79	beql	1b
80	mtpr	$TXDB_BOOT,$TXDB
81	halt
82
83/*
84 * Interrupt vector routines
85 */
86	.globl	_waittime
87
88#define	SCBVEC(name)	.align 2; .globl _X/**/name; _X/**/name
89#define	PANIC(msg)	clrl _waittime; pushab 1f; \
90			calls $1,_panic; 1: .asciz msg
91#define	PRINTF(n,msg)	pushab 1f; calls $n+1,_printf; MSG(msg)
92#define	MSG(msg)	.data; 1: .asciz msg; .text
93#define	PUSHR		pushr $0x3f
94#define	POPR		popr $0x3f
95
96SCBVEC(machcheck):
97	PUSHR; pushab 6*4(sp); calls $1,_machinecheck; POPR;
98	addl2 (sp)+,sp; rei
99SCBVEC(kspnotval):
100	PUSHR; PANIC("KSP not valid");
101SCBVEC(powfail):
102	halt
103SCBVEC(chme): SCBVEC(chms): SCBVEC(chmu):
104	PUSHR; PANIC("CHM? in kernel");
105SCBVEC(stray):
106	PUSHR; PRINTF(0, "stray scb interrupt\n"); POPR;
107	rei
108SCBVEC(nexzvec):
109	PUSHR; mfpr $IPL,-(sp); PRINTF(1, "nexus stray intr ipl%x\n"); POPR; rei
110SCBVEC(cmrd):
111	PUSHR; calls $0,_memerr; POPR; rei
112SCBVEC(wtime):
113	PUSHR; pushl 6*4(sp); PRINTF(1,"write timeout %x\n"); POPR;
114	PANIC("wtimo");
115
116#if NMBA > 0
117SCBVEC(mba3int):
118	PUSHR; pushl $3; brb 1f
119SCBVEC(mba2int):
120	PUSHR; pushl $2; brb 1f
121SCBVEC(mba1int):
122	PUSHR; pushl $1; brb 1f
123SCBVEC(mba0int):
124	PUSHR; pushl $0
1251:	calls $1,_mbintr
126	POPR
127	incl	_cnt+V_INTR
128	rei
129#endif
130
131#if VAX780
132/*
133 * Registers for the uba handling code
134 */
135#define	rUBANUM	r0
136#define	rUBAHD	r1
137#define	rUVEC	r3
138#define	rUBA	r4
139/* r2,r5 are scratch */
140
141SCBVEC(ua3int):
142	PUSHR; movl $3,rUBANUM; moval _uba_hd+(3*UH_SIZE),rUBAHD; brb 1f
143SCBVEC(ua2int):
144	PUSHR; movl $2,rUBANUM; moval _uba_hd+(2*UH_SIZE),rUBAHD; brb 1f
145SCBVEC(ua1int):
146	PUSHR; movl $1,rUBANUM; moval _uba_hd+(1*UH_SIZE),rUBAHD; brb 1f
147SCBVEC(ua0int):
148	PUSHR; movl $0,rUBANUM; moval _uba_hd+(0*UH_SIZE),rUBAHD;
1491:
150	incl	_cnt+V_INTR
151	mfpr	$IPL,r2				/* r2 = mfpr(IPL); */
152	movl	UH_UBA(rUBAHD),rUBA		/* uba = uhp->uh_uba; */
153	movl	UBA_BRRVR-0x14*4(rUBA)[r2],rUVEC
154					/* uvec = uba->uba_brrvr[r2-0x14] */
155ubanorm:
156	bleq	ubaerror
157	addl2	UH_VEC(rUBAHD),rUVEC		/* uvec += uh->uh_vec */
158	bicl3	$3,(rUVEC),r1
159	jmp	2(r1)				/* 2 skips ``pushr $0x3f'' */
160ubaerror:
161	PUSHR; calls $0,_ubaerror; POPR		/* ubaerror r/w's r0-r5 */
162	tstl rUVEC; jneq ubanorm		/* rUVEC contains result */
163	POPR
164	rei
165#endif
166SCBVEC(cnrint):
167	PUSHR; calls $0,_cnrint; POPR; incl _cnt+V_INTR; rei
168SCBVEC(cnxint):
169	PUSHR; calls $0,_cnxint; POPR; incl _cnt+V_INTR; rei
170SCBVEC(hardclock):
171	PUSHR
172	mtpr $ICCS_RUN|ICCS_IE|ICCS_INT|ICCS_ERR,$ICCS
173	pushl 4+6*4(sp); pushl 4+6*4(sp);
174	calls $2,_hardclock			# hardclock(pc,psl)
175#if NPS > 0
176	pushl	4+6*4(sp); pushl 4+6*4(sp);
177	calls	$2,_psextsync
178#endif
179	POPR;
180	incl	_cnt+V_INTR		## temp so not to break vmstat -= HZ
181	rei
182SCBVEC(softclock):
183	PUSHR
184#if NDZ > 0
185	calls	$0,_dztimer
186#endif
187#if NDH > 0
188	calls	$0,_dhtimer
189#endif
190	pushl	4+6*4(sp); pushl 4+6*4(sp);
191	calls	$2,_softclock			# softclock(pc,psl)
192	POPR;
193	rei
194#include "../net/netisr.h"
195	.globl	_netisr
196SCBVEC(netintr):
197	PUSHR
198	bbcc	$NETISR_RAW,_netisr,1f; calls $0,_rawintr; 1:
199#ifdef INET
200#include "../netinet/in_systm.h"
201	bbcc	$NETISR_IP,_netisr,1f; calls $0,_ipintr; 1:
202#endif
203#ifdef NS
204	bbcc	$NETISR_NS,_netisr,1f; calls $0,_nsintr; 1:
205#endif
206	POPR
207	rei
208#if defined(VAX750) || defined(VAX730)
209SCBVEC(consdin):
210	PUSHR;
211#if defined(VAX750) && !defined(MRSP)
212	jsb	tudma
213#endif
214	calls $0,_turintr;
215	POPR;
216	incl _cnt+V_INTR;
217	rei
218SCBVEC(consdout):
219	PUSHR; calls $0,_tuxintr; POPR; incl _cnt+V_INTR; rei
220#else
221SCBVEC(consdin):
222	halt
223SCBVEC(consdout):
224	halt
225#endif
226
227#if NDZ > 0
228/*
229 * DZ pseudo dma routine:
230 *	r0 - controller number
231 */
232	.align	1
233	.globl	dzdma
234dzdma:
235	mull2	$8*20,r0
236	movab	_dzpdma(r0),r3		# pdma structure base
237					# for this controller
238dzploop:
239	movl	r3,r0
240	movl	(r0)+,r1		# device register address
241	movzbl	1(r1),r2		# get line number
242	bitb	$0x80,r2		# TRDY on?
243	beql	dzprei			# no
244	bicb2	$0xf8,r2		# clear garbage bits
245	mull2	$20,r2
246	addl2	r2,r0			# point at line's pdma structure
247	movl	(r0)+,r2		# p_mem
248	cmpl	r2,(r0)+		# p_mem < p_end ?
249	bgequ	dzpcall			# no, go call dzxint
250	movb	(r2)+,6(r1)		# dztbuf = *p_mem++
251	movl	r2,-8(r0)
252	brb 	dzploop			# check for another line
253dzprei:
254	POPR
255	incl	_cnt+V_PDMA
256	rei
257
258dzpcall:
259	pushl	r3
260	pushl	(r0)+			# push tty address
261	calls	$1,*(r0)		# call interrupt rtn
262	movl	(sp)+,r3
263	brb 	dzploop			# check for another line
264#endif
265
266#if NUU > 0 && defined(UUDMA)
267/*
268 * Pseudo DMA routine for tu58 (on DL11)
269 *	r0 - controller number
270 */
271	.align	1
272	.globl	uudma
273uudma:
274	movl	_uudinfo[r0],r2
275	movl	16(r2),r2		# r2 = uuaddr
276	mull3	$48,r0,r3
277	movab	_uu_softc(r3),r5	# r5 = uuc
278
279	cvtwl	2(r2),r1		# c = uuaddr->rdb
280	bbc	$15,r1,1f		# if (c & UUDB_ERROR)
281	movl	$13,16(r5)		#	uuc->tu_state = TUC_RCVERR;
282	rsb				#	let uurintr handle it
2831:
284	tstl	4(r5)			# if (uuc->tu_rcnt) {
285	beql	1f
286	movb	r1,*0(r5)		#	*uuc->tu_rbptr++ = r1
287	incl	(r5)
288	decl	4(r5)			#	if (--uuc->tu_rcnt)
289	beql	2f			#		done
290	tstl	(sp)+
291	POPR				# 	registers saved in ubglue.s
292	rei				# }
2932:
294	cmpl	16(r5),$8		# if (uuc->tu_state != TUS_GETH)
295	beql	2f			# 	let uurintr handle it
2961:
297	rsb
2982:
299	mull2	$14,r0			# sizeof(uudata[ctlr]) = 14
300	movab	_uudata(r0),r4		# data = &uudata[ctlr];
301	cmpb	$1,(r4)			# if (data->pk_flag != TUF_DATA)
302	bneq	1b
303#ifdef notdef
304	/* this is for command packets */
305	beql	1f			# 	r0 = uuc->tu_rbptr
306	movl	(r5),r0
307	brb	2f
3081:					# else
309#endif
310	movl	24(r5),r0		# 	r0 = uuc->tu_addr
3112:
312	movzbl	1(r4),r3		# counter to r3 (data->pk_count)
313	movzwl	(r4),r1			# first word of checksum (=header)
314	mfpr	$IPL,-(sp)		# s = spl5();
315	mtpr	$0x15,$IPL		# to keep disk interrupts out
316	clrw	(r2)			# disable receiver interrupts
3173:	bbc	$7,(r2),3b		# while ((uuaddr->rcs & UUCS_READY)==0);
318	cvtwb	2(r2),(r0)+		# *buffer = uuaddr->rdb & 0xff
319	sobgtr	r3,1f			# continue with next byte ...
320	addw2	2(r2),r1		# unless this was the last (odd count)
321	brb	2f
322
3231:	bbc	$7,(r2),1b		# while ((uuaddr->rcs & UUCS_READY)==0);
324	cvtwb	2(r2),(r0)+		# *buffer = uuaddr->rdb & 0xff
325	addw2	-2(r0),r1		# add to checksum..
3262:
327	adwc	$0,r1			# get the carry
328	sobgtr	r3,3b			# loop while r3 > 0
329/*
330 * We're ready to get the checksum
331 */
3321:	bbc	$7,(r2),1b		# while ((uuaddr->rcs & UUCS_READY)==0);
333	cvtwb	2(r2),12(r4)		# get first (lower) byte
3341:	bbc	$7,(r2),1b
335	cvtwb	2(r2),13(r4)		# ..and second
336	cmpw	12(r4),r1		# is checksum ok?
337	beql	1f
338	movl	$14,16(r5)		# uuc->tu_state = TUS_CHKERR
339	brb	2f			# exit
3401:
341	movl	$11,16(r5)		# uuc->tu_state = TUS_GET (ok)
3422:
343	movw	$0x40,(r2)		# enable receiver interrupts
344	mtpr	(sp)+,$IPL		# splx(s);
345	rsb				# continue processing in uurintr
346#endif
347
348#if defined(VAX750) && !defined(MRSP)
349/*
350 * Pseudo DMA routine for console tu58
351 *   	    (without MRSP)
352 */
353	.align	1
354	.globl	tudma
355tudma:
356	movab	_tu,r5			# r5 = tu
357	tstl	4(r5)			# if (tu.tu_rcnt) {
358	beql	3f
359	mfpr	$CSRD,r1		# get data from tu58
360	movb	r1,*0(r5)		#	*tu.tu_rbptr++ = r1
361	incl	(r5)
362	decl	4(r5)			#	if (--tu.tu_rcnt)
363	beql	1f			#		done
364	tstl	(sp)+
365	POPR				# 	registers saved in ubglue.s
366	rei				# 	data handled, done
3671:					# }
368	cmpl	16(r5),$8		# if (tu.tu_state != TUS_GETH)
369	beql	2f			# 	let turintr handle it
3703:
371	rsb
3722:
373	movab	_tudata,r4		# r4 = tudata
374	cmpb	$1,(r4)			# if (tudata.pk_flag != TUF_DATA)
375	bneq	3b			# 	let turintr handle it
3761:					# else
377	movl	24(r5),r1		# get buffer pointer to r1
378	movzbl	1(r4),r3		# counter to r3
379	movzwl	(r4),r0			# first word of checksum (=header)
380	mtpr	$0,$CSRS		# disable receiver interrupts
3813:
382	bsbw	5f			# wait for next byte
383	mfpr	$CSRD,r5
384	movb	r5,(r1)+		# *buffer = rdb
385	sobgtr	r3,1f			# continue with next byte ...
386	mfpr	$CSRD,r2		# unless this was the last (odd count)
387	brb	2f
388
3891:	bsbw	5f			# wait for next byte
390	mfpr	$CSRD,r5
391	movb	r5,(r1)+		# *buffer = rdb
392	movzwl	-2(r1),r2		# get the last word back from memory
3932:
394	addw2	r2,r0			# add to checksum..
395	adwc	$0,r0			# get the carry
396	sobgtr	r3,3b			# loop while r3 > 0
397/*
398 * We're ready to get the checksum.
399 */
400	bsbw	5f
401	movab	_tudata,r4
402	mfpr	$CSRD,r5
403	movb	r5,12(r4)		# get first (lower) byte
404	bsbw	5f
405	mfpr	$CSRD,r5
406	movb	r5,13(r4)		# ..and second
407	movab	_tu,r5
408	cmpw	12(r4),r0		# is checksum ok?
409	beql	1f
410	movl	$14,16(r5)		# tu.tu_state = TUS_CHKERR
411	brb	2f			# exit
4121:
413	movl	$11,16(r5)		# tu.tu_state = TUS_GET
4142:
415	mtpr	$0x40,$CSRS		# enable receiver interrupts
416	rsb				# continue processing in turintr
417/*
418 * Loop until a new byte is ready from
419 * the tu58, make sure we don't loop forever
420 */
4215:
422	mfpr	$IPL,-(sp)		# can't loop at ipl7, better
423	mtpr	$0x15,$IPL		# move down to 5
424	movl	$5000,r5		# loop max 5000 times
4251:
426	mfpr	$CSRS,r2
427	bbs	$7,r2,1f
428	sobgtr	r5,1b
429	movab	_tu,r5
430	movl	$13,16(r5)		# return TUS_RCVERR
431	mtpr	(sp)+,$IPL
432	tstl	(sp)+			# and let turintr handle it
433	rsb				# before we go back to turintr
4341:
435	mtpr	(sp)+,$IPL
436	rsb
437#endif
438
439/*
440 * Stray UNIBUS interrupt catch routines
441 */
442	.data
443	.align	2
444#define	PJ	PUSHR;jsb _Xustray
445	.globl	_catcher
446_catcher:
447	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
448	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
449	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
450	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
451	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
452	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
453	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
454	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
455
456	.globl	_cold
457_cold:	.long	1
458	.data
459
460	.text
461SCBVEC(ustray):
462	blbc	_cold,1f
463	mfpr	$IPL,r11
464	subl3	$_catcher+8,(sp)+,r10
465	ashl	$-1,r10,r10
466	POPR
467	rei
4681:
469	subl3	$_catcher+8,(sp)+,r0
470	ashl	$-1,r0,-(sp)
471	mfpr	$IPL,-(sp)
472	PRINTF(2, "uba?: stray intr ipl %x vec %o\n")
473	POPR
474	rei
475
476/*
477 * Trap and fault vector routines
478 */
479#define	TRAP(a)	pushl $T_/**/a; jbr alltraps
480
481/*
482 * Ast delivery (profiling and/or reschedule)
483 */
484SCBVEC(astflt):
485	pushl $0; TRAP(ASTFLT)
486SCBVEC(privinflt):
487	pushl $0; TRAP(PRIVINFLT)
488SCBVEC(xfcflt):
489	pushl $0; TRAP(XFCFLT)
490SCBVEC(resopflt):
491	pushl $0; TRAP(RESOPFLT)
492SCBVEC(resadflt):
493	pushl $0; TRAP(RESADFLT)
494SCBVEC(bptflt):
495	pushl $0; TRAP(BPTFLT)
496SCBVEC(compatflt):
497	TRAP(COMPATFLT);
498SCBVEC(tracep):
499	pushl $0; TRAP(TRCTRAP)
500SCBVEC(arithtrap):
501	TRAP(ARITHTRAP)
502SCBVEC(protflt):
503	blbs	(sp)+,segflt
504	TRAP(PROTFLT)
505segflt:
506	TRAP(SEGFLT)
507SCBVEC(transflt):
508	bitl	$2,(sp)+
509	bnequ	tableflt
510	jsb	Fastreclaim		# try and avoid pagein
511	TRAP(PAGEFLT)
512tableflt:
513	TRAP(TABLEFLT)
514
515alltraps:
516	mfpr	$USP,-(sp); calls $0,_trap; mtpr (sp)+,$USP
517	incl	_cnt+V_TRAP
518	addl2	$8,sp			# pop type, code
519	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
520	rei
521
522SCBVEC(syscall):
523	pushl	$T_SYSCALL
524	mfpr	$USP,-(sp); calls $0,_syscall; mtpr (sp)+,$USP
525	incl	_cnt+V_SYSCALL
526	addl2	$8,sp			# pop type, code
527	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
528	rei
529
530/*
531 * System page table
532 */
533#define	vaddr(x)	((((x)-_Sysmap)/4)*NBPG+0x80000000)
534#define	SYSMAP(mname, vname, npte)			\
535_/**/mname:	.globl	_/**/mname;		\
536	.space	npte*4;				\
537	.globl	_/**/vname;			\
538	.set	_/**/vname,vaddr(_/**/mname)
539
540	.data
541	.align	2
542	SYSMAP(Sysmap	,Sysbase	,SYSPTSIZE	)
543	SYSMAP(UMBAbeg	,umbabeg	,0		)
544	SYSMAP(Nexmap	,nexus		,16*MAXNNEXUS	)
545	SYSMAP(UMEMmap	,umem		,512*MAXNUBA	)
546	SYSMAP(UMBAend	,umbaend	,0		)
547	SYSMAP(Usrptmap	,usrpt		,USRPTSIZE	)
548	SYSMAP(Forkmap	,forkutl	,UPAGES		)
549	SYSMAP(Xswapmap	,xswaputl	,UPAGES		)
550	SYSMAP(Xswap2map,xswap2utl	,UPAGES		)
551	SYSMAP(Swapmap	,swaputl	,UPAGES		)
552	SYSMAP(Pushmap	,pushutl	,UPAGES		)
553	SYSMAP(Vfmap	,vfutl		,UPAGES		)
554	SYSMAP(CMAP1	,CADDR1		,1		)
555	SYSMAP(CMAP2	,CADDR2		,1		)
556	SYSMAP(mcrmap	,mcr		,1		)
557	SYSMAP(mmap	,vmmap		,1		)
558	SYSMAP(msgbufmap,msgbuf		,MSGBUFPTECNT	)
559	SYSMAP(camap	,cabase		,16*CLSIZE	)
560	SYSMAP(ecamap	,calimit	,0		)
561	SYSMAP(Mbmap	,mbutl		,NMBCLUSTERS*CLSIZE)
562
563eSysmap:
564	.globl	_Syssize
565	.set	_Syssize,(eSysmap-_Sysmap)/4
566	.text
567
568/*
569 * Initialization
570 *
571 * ipl 0x1f; mapen 0; scbb, pcbb, sbr, slr, isp, ksp not set
572 */
573	.data
574	.globl	_cpu
575_cpu:	.long	0
576	.text
577	.globl	start
578start:
579	.word	0
580/* set system control block base and system page table params */
581	mtpr	$_scb-0x80000000,$SCBB
582	mtpr	$_Sysmap-0x80000000,$SBR
583	mtpr	$_Syssize,$SLR
584/* double map the kernel into the virtual user addresses of phys mem */
585	mtpr	$_Sysmap,$P0BR
586	mtpr	$_Syssize,$P0LR
587/* set ISP and get cpu type */
588	movl	$_intstack+NISP*NBPG,sp
589	mfpr	$SID,r0
590	movab	_cpu,r1
591	extzv	$24,$8,r0,(r1)
592/* init RPB */
593	movab	_rpb,r0
594	movl	r0,(r0)+			# rp_selfref
595	movab	_doadump,r1
596	movl	r1,(r0)+			# rp_dumprout
597	movl	$0x1f,r2
598	clrl	r3
5991:	addl2	(r1)+,r3; sobgtr r2,1b
600	movl	r3,(r0)+			# rp_chksum
601/* count up memory */
602	clrl	r7
6031:	pushl	$4; pushl r7; calls $2,_badaddr; tstl r0; bneq 9f
604	acbl	$8192*1024-1,$64*1024,r7,1b
6059:
606/* clear memory from kernel bss and pages for proc 0 u. and page table */
607	movab	_edata,r6
608	movab	_end,r5
609	bbcc	$31,r5,0f; 0:
610	addl2	$(UPAGES*NBPG)+NBPG+NBPG,r5
6111:	clrq	(r6); acbl r5,$8,r6,1b
612/* trap() and syscall() save r0-r11 in the entry mask (per ../h/reg.h) */
613	bisw2	$0x0fff,_trap
614	bisw2	$0x0fff,_syscall
615	calls	$0,_fixctlrmask
616/* initialize system page table: scb and int stack writeable */
617	clrl	r2
618	movab	eintstack,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
6191:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
620/* make rpb read-only as red zone for interrupt stack */
621	bicl2	$PG_PROT,_rpbmap
622	bisl2	$PG_KR,_rpbmap
623/* make kernel text space read-only */
624	movab	_etext+NBPG-1,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
6251:	bisl3	$PG_V|PG_KR,r2,_Sysmap[r2]; aoblss r1,r2,1b
626/* make kernel data, bss, read-write */
627	movab	_end+NBPG-1,r1; bbcc $31,r1,0f; 0:; ashl $-PGSHIFT,r1,r1
6281:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
629/* now go to mapped mode */
630	mtpr	$1,$TBIA; mtpr $1,$MAPEN; jmp *$0f; 0:
631/* init mem sizes */
632	ashl	$-PGSHIFT,r7,_maxmem
633	movl	_maxmem,_physmem
634	movl	_maxmem,_freemem
635/* setup context for proc[0] == Scheduler */
636	movab	_end+NBPG-1,r6
637	bicl2	$NBPG-1,r6		# make page boundary
638/* setup page table for proc[0] */
639	bbcc	$31,r6,0f; 0:
640	ashl	$-PGSHIFT,r6,r3			# r3 = btoc(r6)
641	bisl3	$PG_V|PG_KW,r3,_Usrptmap	# init first upt entry
642	incl	r3
643	movab	_usrpt,r0
644	mtpr	r0,$TBIS
645/* init p0br, p0lr */
646	mtpr	r0,$P0BR
647	mtpr	$0,$P0LR
648/* init p1br, p1lr */
649	movab	NBPG(r0),r0
650	movl	$0x200000-UPAGES,r1
651	mtpr	r1,$P1LR
652	mnegl	r1,r1
653	moval	-4*UPAGES(r0)[r1],r2
654	mtpr	r2,$P1BR
655/* setup mapping for UPAGES of _u */
656	movl	$UPAGES,r2; movab _u+NBPG*UPAGES,r1; addl2 $UPAGES,r3; jbr 2f
6571:	decl	r3
658	moval	-NBPG(r1),r1;
659	bisl3	$PG_V|PG_URKW,r3,-(r0)
660	mtpr	r1,$TBIS
6612:	sobgeq	r2,1b
662/* initialize (slightly) the pcb */
663	movab	UPAGES*NBPG(r1),PCB_KSP(r1)
664	mnegl	$1,PCB_ESP(r1)
665	mnegl	$1,PCB_SSP(r1)
666	movl	r1,PCB_USP(r1)
667	mfpr	$P0BR,PCB_P0BR(r1)
668	mfpr	$P0LR,PCB_P0LR(r1)
669	movb	$4,PCB_P0LR+3(r1)		# disable ast
670	mfpr	$P1BR,PCB_P1BR(r1)
671	mfpr	$P1LR,PCB_P1LR(r1)
672	movl	$CLSIZE,PCB_SZPT(r1)		# init u.u_pcb.pcb_szpt
673	movl	r11,PCB_R11(r1)
674	movab	1f,PCB_PC(r1)			# initial pc
675	clrl	PCB_PSL(r1)			# mode(k,k), ipl=0
676	ashl	$PGSHIFT,r3,r3
677	mtpr	r3,$PCBB			# first pcbb
678/* set regs, p0br, p0lr, p1br, p1lr, astlvl, ksp and change to kernel mode */
679	ldpctx
680	rei
681/* put signal trampoline code in u. area */
6821:	movab	_u,r0
683	movc3	$16,sigcode,PCB_SIGC(r0)
684/* save reboot flags in global _boothowto */
685	movl	r11,_boothowto
686/* calculate firstaddr, and call main() */
687	movab	_end+NBPG-1,r0; bbcc $31,r0,0f; 0:; ashl $-PGSHIFT,r0,-(sp)
688	addl2	$UPAGES+1,(sp); calls $1,_main
689/* proc[1] == /etc/init now running here; run icode */
690	pushl	$PSL_CURMOD|PSL_PRVMOD; pushl $0; rei
691
692/* signal trampoline code: it is known that this code takes exactly 16 bytes */
693/* in ../vax/pcb.h and in the movc3 above */
694sigcode:
695	calls	$4,5(pc)			# params pushed by sendsig
696	chmk	$139				# cleanup mask and onsigstack
697	rei
698	.word	0x7f				# registers 0-6 (6==sp/compat)
699	callg	(ap),*16(ap)
700	ret
701
702/*
703 * Primitives
704 */
705
706/*
707 * badaddr(addr, len)
708 *	see if access addr with a len type instruction causes a machine check
709 *	len is length of access (1=byte, 2=short, 4=long)
710 */
711	.globl	_badaddr
712_badaddr:
713	.word	0
714	movl	$1,r0
715	mfpr	$IPL,r1
716	mtpr	$HIGH,$IPL
717	movl	_scb+MCKVEC,r2
718	movl	4(ap),r3
719	movl	8(ap),r4
720	movab	9f+INTSTK,_scb+MCKVEC
721	bbc	$0,r4,1f; tstb	(r3)
7221:	bbc	$1,r4,1f; tstw	(r3)
7231:	bbc	$2,r4,1f; tstl	(r3)
7241:	clrl	r0			# made it w/o machine checks
7252:	movl	r2,_scb+MCKVEC
726	mtpr	r1,$IPL
727	ret
728	.align	2
7299:
730	casel	_cpu,$1,$VAX_MAX
7310:
732	.word	8f-0b		# 1 is 780
733	.word	5f-0b		# 2 is 750
734	.word	5f-0b		# 3 is 730
7355:
736#if defined(VAX750) || defined(VAX730)
737	mtpr	$0xf,$MCESR
738#endif
739	brb	1f
7408:
741#if VAX780
742	mtpr	$0,$SBIFS
743#endif
7441:
745	addl2	(sp)+,sp		# discard mchchk trash
746	movab	2b,(sp)
747	rei
748
749_addupc:	.globl	_addupc
750	.word	0x0
751	movl	8(ap),r2		# &u.u_prof
752	subl3	8(r2),4(ap),r0		# corrected pc
753	blss	9f
754	extzv	$1,$31,r0,r0		# logical right shift
755	extzv	$1,$31,12(r2),r1	# ditto for scale
756	emul	r1,r0,$0,r0
757	ashq	$-14,r0,r0
758	tstl	r1
759	bneq	9f
760	bicl2	$1,r0
761	cmpl	r0,4(r2)		# length
762	bgequ	9f
763	addl2	(r2),r0			# base
764	probew	$3,$2,(r0)
765	beql	8f
766	addw2	12(ap),(r0)
7679:
768	ret
7698:
770	clrl	12(r2)
771	ret
772
773_Copyin:	.globl	_Copyin		# <<<massaged for jsb by asm.sed>>>
774	movl	12(sp),r0		# copy length
775	blss	ersb
776	movl	4(sp),r1		# copy user address
777	cmpl	$NBPG,r0		# probing one page or less ?
778	bgeq	cishort			# yes
779ciloop:
780	prober	$3,$NBPG,(r1)		# bytes accessible ?
781	beql	ersb			# no
782	addl2	$NBPG,r1		# incr user address ptr
783	acbl	$NBPG+1,$-NBPG,r0,ciloop	# reduce count and loop
784cishort:
785	prober	$3,r0,(r1)		# bytes accessible ?
786	beql	ersb			# no
787	movl	4(sp),r1
788	movl	8(sp),r3
789	jbr	2f
7901:
791	subl2	r0,12(sp)
792	movc3	r0,(r1),(r3)
7932:
794	movzwl	$65535,r0
795	cmpl	12(sp),r0
796	jgtr	1b
797	movc3	12(sp),(r1),(r3)
798	clrl	r0			#redundant
799	rsb
800
801ersb:
802	movl	$EFAULT,r0
803	rsb
804
805_Copyout: 	.globl	_Copyout	# <<<massaged for jsb by asm.sed >>>
806	movl	12(sp),r0		# get count
807	blss	ersb
808	movl	8(sp),r1		# get user address
809	cmpl	$NBPG,r0		# can do in one probew?
810	bgeq	coshort			# yes
811coloop:
812	probew	$3,$NBPG,(r1)		# bytes accessible?
813	beql	ersb			# no
814	addl2	$NBPG,r1		# increment user address
815	acbl	$NBPG+1,$-NBPG,r0,coloop	# reduce count and loop
816coshort:
817	probew	$3,r0,(r1)		# bytes accessible?
818	beql	ersb			# no
819	movl	4(sp),r1
820	movl	8(sp),r3
821	jbr	2f
8221:
823	subl2	r0,12(sp)
824	movc3	r0,(r1),(r3)
8252:
826	movzwl	$65535,r0
827	cmpl	12(sp),r0
828	jgtr	1b
829	movc3	12(sp),(r1),(r3)
830	clrl	r0				#redundant
831	rsb
832
833/*
834 * non-local goto's
835 */
836	.globl	_Setjmp
837_Setjmp:
838	movq	r6,(r0)+
839	movq	r8,(r0)+
840	movq	r10,(r0)+
841	movq	r12,(r0)+
842	addl3	$4,sp,(r0)+
843	movl	(sp),(r0)
844	clrl	r0
845	rsb
846
847	.globl	_Longjmp
848_Longjmp:
849	movq	(r0)+,r6
850	movq	(r0)+,r8
851	movq	(r0)+,r10
852	movq	(r0)+,r12
853	movl	(r0)+,r1
854	cmpl	r1,sp				# must be a pop
855	bgequ	lj2
856	pushab	lj1
857	calls	$1,_panic
858lj2:
859	movl	r1,sp
860	jmp	*(r0)				# ``rsb''
861
862lj1:	.asciz	"longjmp"
863
864	.globl	_whichqs
865	.globl	_qs
866	.globl	_cnt
867
868	.globl	_noproc
869	.comm	_noproc,4
870	.globl	_runrun
871	.comm	_runrun,4
872
873/*
874 * The following primitives use the fancy VAX instructions
875 * much like VMS does.  _whichqs tells which of the 32 queues _qs
876 * have processes in them.  Setrq puts processes into queues, Remrq
877 * removes them from queues.  The running process is on no queue,
878 * other processes are on a queue related to p->p_pri, divided by 4
879 * actually to shrink the 0-127 range of priorities into the 32 available
880 * queues.
881 */
882
883/*
884 * Setrq(p), using fancy VAX instructions.
885 *
886 * Call should be made at spl6(), and p->p_stat should be SRUN
887 */
888	.globl	_Setrq		# <<<massaged to jsb by "asm.sed">>>
889_Setrq:
890	tstl	P_RLINK(r0)		## firewall: p->p_rlink must be 0
891	beql	set1			##
892	pushab	set3			##
893	calls	$1,_panic		##
894set1:
895	movzbl	P_PRI(r0),r1		# put on queue which is p->p_pri / 4
896	ashl	$-2,r1,r1
897	movaq	_qs[r1],r2
898	insque	(r0),*4(r2)		# at end of queue
899	bbss	r1,_whichqs,set2	# mark queue non-empty
900set2:
901	rsb
902
903set3:	.asciz	"setrq"
904
905/*
906 * Remrq(p), using fancy VAX instructions
907 *
908 * Call should be made at spl6().
909 */
910	.globl	_Remrq		# <<<massaged to jsb by "asm.sed">>>
911_Remrq:
912	movzbl	P_PRI(r0),r1
913	ashl	$-2,r1,r1
914	bbsc	r1,_whichqs,rem1
915	pushab	rem3			# it wasn't recorded to be on its q
916	calls	$1,_panic
917rem1:
918	remque	(r0),r2
919	beql	rem2
920	bbss	r1,_whichqs,rem2
921rem2:
922	clrl	P_RLINK(r0)		## for firewall checking
923	rsb
924
925rem3:	.asciz	"remrq"
926
927/*
928 * Masterpaddr is the p->p_addr of the running process on the master
929 * processor.  When a multiprocessor system, the slave processors will have
930 * an array of slavepaddr's.
931 */
932	.globl	_masterpaddr
933	.data
934_masterpaddr:
935	.long	0
936
937	.text
938sw0:	.asciz	"swtch"
939/*
940 * Swtch(), using fancy VAX instructions
941 */
942	.globl	_Swtch
943_Swtch:				# <<<massaged to jsb by "asm.sed">>>
944	movl	$1,_noproc
945	clrl	_runrun
946sw1:	ffs	$0,$32,_whichqs,r0	# look for non-empty queue
947	bneq	sw1a
948	mtpr	$0,$IPL			# must allow interrupts here
949	jbr	sw1			# this is an idle loop!
950sw1a:	mtpr	$0x18,$IPL		# lock out all so _whichqs==_qs
951	bbcc	r0,_whichqs,sw1		# proc moved via lbolt interrupt
952	movaq	_qs[r0],r1
953	remque	*(r1),r2		# r2 = p = highest pri process
954	bvc	sw2			# make sure something was there
955sw1b:	pushab	sw0
956	calls	$1,_panic
957sw2:	beql	sw3
958	insv	$1,r0,$1,_whichqs	# still more procs in this queue
959sw3:
960	clrl	_noproc
961	tstl	P_WCHAN(r2)		## firewalls
962	bneq	sw1b			##
963	movzbl	P_STAT(r2),r3		##
964	cmpl	$SRUN,r3		##
965	bneq	sw1b			##
966	clrl	P_RLINK(r2)		##
967	movl	*P_ADDR(r2),r0
968	movl	r0,_masterpaddr
969	ashl	$PGSHIFT,r0,r0		# r0 = pcbb(p)
970/*	mfpr	$PCBB,r1		# resume of current proc is easy
971 *	cmpl	r0,r1
972 */	beql	res0
973	incl	_cnt+V_SWTCH
974/* fall into... */
975
976/*
977 * Resume(pf)
978 */
979	.globl	_Resume		# <<<massaged to jsb by "asm.sed">>>
980_Resume:
981	mtpr	$0x18,$IPL			# no interrupts, please
982	movl	_CMAP2,_u+PCB_CMAP2	# yech
983	svpctx
984	mtpr	r0,$PCBB
985	ldpctx
986	movl	_u+PCB_CMAP2,_CMAP2	# yech
987	mtpr	$_CADDR2,$TBIS
988res0:
989	tstl	_u+PCB_SSWAP
990	beql	res1
991	movl	_u+PCB_SSWAP,r0
992	clrl	_u+PCB_SSWAP
993	movab	_Longjmp,(sp)
994	movl	$PSL_PRVMOD,4(sp)		# ``cheating'' (jfr)
995res1:
996	rei
997
998/*
999 * {fu,su},{byte,word}, all massaged by asm.sed to jsb's
1000 */
1001	.globl	_Fuword
1002_Fuword:
1003	prober	$3,$4,(r0)
1004	beql	fserr
1005	movl	(r0),r0
1006	rsb
1007fserr:
1008	mnegl	$1,r0
1009	rsb
1010
1011	.globl	_Fubyte
1012_Fubyte:
1013	prober	$3,$1,(r0)
1014	beql	fserr
1015	movzbl	(r0),r0
1016	rsb
1017
1018	.globl	_Suword
1019_Suword:
1020	probew	$3,$4,(r0)
1021	beql	fserr
1022	movl	r1,(r0)
1023	clrl	r0
1024	rsb
1025
1026	.globl	_Subyte
1027_Subyte:
1028	probew	$3,$1,(r0)
1029	beql	fserr
1030	movb	r1,(r0)
1031	clrl	r0
1032	rsb
1033
1034/*
1035 * Copy 1 relocation unit (NBPG bytes)
1036 * from user virtual address to physical address
1037 */
1038_copyseg: 	.globl	_copyseg
1039	.word	0x0
1040	bisl3	$PG_V|PG_KW,8(ap),_CMAP2
1041	mtpr	$_CADDR2,$TBIS	# invalidate entry for copy
1042	movc3	$NBPG,*4(ap),_CADDR2
1043	ret
1044
1045/*
1046 * zero out physical memory
1047 * specified in relocation units (NBPG bytes)
1048 */
1049_clearseg: 	.globl	_clearseg
1050	.word	0x0
1051	bisl3	$PG_V|PG_KW,4(ap),_CMAP1
1052	mtpr	$_CADDR1,$TBIS
1053	movc5	$0,(sp),$0,$NBPG,_CADDR1
1054	ret
1055
1056/*
1057 * Check address.
1058 * Given virtual address, byte count, and rw flag
1059 * returns 0 on no access.
1060 */
1061_useracc:	.globl	_useracc
1062	.word	0x0
1063	movl	4(ap),r0		# get va
1064	movl	8(ap),r1		# count
1065	tstl	12(ap)			# test for read access ?
1066	bneq	userar			# yes
1067	cmpl	$NBPG,r1			# can we do it in one probe ?
1068	bgeq	uaw2			# yes
1069uaw1:
1070	probew	$3,$NBPG,(r0)
1071	beql	uaerr			# no access
1072	addl2	$NBPG,r0
1073	acbl	$NBPG+1,$-NBPG,r1,uaw1
1074uaw2:
1075	probew	$3,r1,(r0)
1076	beql	uaerr
1077	movl	$1,r0
1078	ret
1079
1080userar:
1081	cmpl	$NBPG,r1
1082	bgeq	uar2
1083uar1:
1084	prober	$3,$NBPG,(r0)
1085	beql	uaerr
1086	addl2	$NBPG,r0
1087	acbl	$NBPG+1,$-NBPG,r1,uar1
1088uar2:
1089	prober	$3,r1,(r0)
1090	beql	uaerr
1091	movl	$1,r0
1092	ret
1093uaerr:
1094	clrl	r0
1095	ret
1096
1097/*
1098 * kernacc - check for kernel access privileges
1099 *
1100 * We can't use the probe instruction directly because
1101 * it ors together current and previous mode.
1102 */
1103	.globl	_kernacc
1104_kernacc:
1105	.word	0x0
1106	movl	4(ap),r0	# virtual address
1107	bbcc	$31,r0,kacc1
1108	bbs	$30,r0,kacerr
1109	mfpr	$SBR,r2		# address and length of page table (system)
1110	bbss	$31,r2,0f; 0:
1111	mfpr	$SLR,r3
1112	brb	kacc2
1113kacc1:
1114	bbsc	$30,r0,kacc3
1115	mfpr	$P0BR,r2	# user P0
1116	mfpr	$P0LR,r3
1117	brb	kacc2
1118kacc3:
1119	mfpr	$P1BR,r2	# user P1 (stack)
1120	mfpr	$P1LR,r3
1121kacc2:
1122	addl3	8(ap),r0,r1	# ending virtual address
1123	addl2	$NBPG-1,r1
1124	ashl	$-PGSHIFT,r0,r0
1125	ashl	$-PGSHIFT,r1,r1
1126	bbs	$31,4(ap),kacc6
1127	bbc	$30,4(ap),kacc6
1128	cmpl	r0,r3		# user stack
1129	blss	kacerr		# address too low
1130	brb	kacc4
1131kacc6:
1132	cmpl	r1,r3		# compare last page to P0LR or SLR
1133	bgtr	kacerr		# address too high
1134kacc4:
1135	movl	(r2)[r0],r3
1136	bbc	$31,4(ap),kacc4a
1137	bbc	$31,r3,kacerr	# valid bit is off
1138kacc4a:
1139	cmpzv	$27,$4,r3,$1	# check protection code
1140	bleq	kacerr		# no access allowed
1141	tstb	12(ap)
1142	bneq	kacc5		# only check read access
1143	cmpzv	$27,$2,r3,$3	# check low 2 bits of prot code
1144	beql	kacerr		# no write access
1145kacc5:
1146	aoblss	r1,r0,kacc4	# next page
1147	movl	$1,r0		# no errors
1148	ret
1149kacerr:
1150	clrl	r0		# error
1151	ret
1152/*
1153 * Extracted and unrolled most common case of pagein (hopefully):
1154 *	resident and not on free list (reclaim of page is purely
1155 *	for the purpose of simulating a reference bit)
1156 *
1157 * Built in constants:
1158 *	CLSIZE of 2, USRSTACK of 0x7ffff000, any bit fields
1159 *	in pte's or the core map
1160 */
1161	.text
1162	.globl	Fastreclaim
1163Fastreclaim:
1164	PUSHR
1165	extzv	$9,$23,28(sp),r3	# virtual address
1166	bicl2	$1,r3			# v = clbase(btop(virtaddr));
1167	movl	_u+U_PROCP,r5		# p = u.u_procp
1168					# from vtopte(p, v) ...
1169	cmpl	r3,P_TSIZE(r5)
1170	jgequ	2f			# if (isatsv(p, v)) {
1171	ashl	$2,r3,r4
1172	addl2	P_P0BR(r5),r4		#	tptopte(p, vtotp(p, v));
1173	movl	$1,r2			#	type = CTEXT;
1174	jbr	3f
11752:
1176	subl3	P_SSIZE(r5),$0x3ffff8,r0
1177	cmpl	r3,r0
1178	jgequ	2f			# } else if (isadsv(p, v)) {
1179	ashl	$2,r3,r4
1180	addl2	P_P0BR(r5),r4		#	dptopte(p, vtodp(p, v));
1181	clrl	r2			#	type = !CTEXT;
1182	jbr	3f
11832:
1184	cvtwl	P_SZPT(r5),r4		# } else (isassv(p, v)) {
1185	ashl	$7,r4,r4
1186	subl2	$(0x3ffff8+UPAGES),r4
1187	addl2	r3,r4
1188	ashl	$2,r4,r4
1189	addl2	P_P0BR(r5),r4		#	sptopte(p, vtosp(p, v));
1190	clrl	r2			# 	type = !CTEXT;
11913:					# }
1192	bitb	$0x82,3(r4)
1193	beql	2f			# if (pte->pg_v || pte->pg_fod)
1194	POPR; rsb			#	let pagein handle it
11952:
1196	bicl3	$0xffe00000,(r4),r0
1197	jneq	2f			# if (pte->pg_pfnum == 0)
1198	POPR; rsb			# 	let pagein handle it
11992:
1200	subl2	_firstfree,r0
1201	ashl	$-1,r0,r0
1202	incl	r0			# pgtocm(pte->pg_pfnum)
1203	mull2	$12,r0
1204	addl2	_cmap,r0		# &cmap[pgtocm(pte->pg_pfnum)]
1205	tstl	r2
1206	jeql	2f			# if (type == CTEXT &&
1207	jbc	$29,4(r0),2f		#     c_intrans)
1208	POPR; rsb			# 	let pagein handle it
12092:
1210	jbc	$30,4(r0),2f		# if (c_free)
1211	POPR; rsb			# 	let pagein handle it
12122:
1213	bisb2	$0x80,3(r4)		# pte->pg_v = 1;
1214	jbc	$26,4(r4),2f		# if (anycl(pte, pg_m)
1215	bisb2	$0x04,3(r4)		#	pte->pg_m = 1;
12162:
1217	bicw3	$0x7f,2(r4),r0
1218	bicw3	$0xff80,6(r4),r1
1219	bisw3	r0,r1,6(r4)		# distcl(pte);
1220	ashl	$PGSHIFT,r3,r0
1221	mtpr	r0,$TBIS
1222	addl2	$NBPG,r0
1223	mtpr	r0,$TBIS		# tbiscl(v);
1224	tstl	r2
1225	jeql	2f			# if (type == CTEXT)
1226	movl	P_TEXTP(r5),r0
1227	movl	X_CADDR(r0),r5		# for (p = p->p_textp->x_caddr; p; ) {
1228	jeql	2f
1229	ashl	$2,r3,r3
12303:
1231	addl3	P_P0BR(r5),r3,r0	#	tpte = tptopte(p, tp);
1232	bisb2	$1,P_FLAG+3(r5)		#	p->p_flag |= SPTECHG;
1233	movl	(r4),(r0)+		#	for (i = 0; i < CLSIZE; i++)
1234	movl	4(r4),(r0)		#		tpte[i] = pte[i];
1235	movl	P_XLINK(r5),r5		#	p = p->p_xlink;
1236	jneq	3b			# }
12372:					# collect a few statistics...
1238	incl	_cnt+V_FAULTS		# cnt.v_faults++;
1239	incl	_u+U_RU+RU_MINFLT	# u.u_ru.ru_minflt++;
1240	incl	_cnt+V_PGREC		# cnt.v_pgrec++;
1241	incl	_cnt+V_FASTPGREC	# cnt.v_fastpgrec++;
1242	incl	_cnt+V_TRAP		# cnt.v_trap++;
1243	POPR
1244	addl2	$8,sp			# pop pc, code
1245	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
1246	rei
1247