xref: /original-bsd/sys/vax/vax/locore.s (revision 23c6a147)
1/*
2 * Copyright (c) 1980, 1986 Regents of the University of California.
3 * All rights reserved.  The Berkeley software License Agreement
4 * specifies the terms and conditions for redistribution.
5 *
6 *	@(#)locore.s	7.24 (Berkeley) 05/10/90
7 */
8
9#include "psl.h"
10#include "pte.h"
11
12#include "errno.h"
13#include "syscall.h"
14#include "cmap.h"
15
16#include "mtpr.h"
17#include "trap.h"
18#include "cpu.h"
19#include "nexus.h"
20#include "cons.h"
21#include "clock.h"
22#include "ioa.h"
23#include "ka630.h"
24#include "ka650.h"
25#include "ka820.h"
26#include "../vaxuba/ubareg.h"
27
28#include "dz.h"
29#include "uu.h"
30#include "ps.h"
31#include "mba.h"
32#include "uba.h"
33
34	.set	HIGH,0x1f	# mask for total disable
35	.set	MCKVEC,4	# offset into scb of machine check vector
36	.set	NBPG,512
37	.set	PGSHIFT,9
38	.set	SYSTEM,0x80000000	# virtual address of system start
39
40	.set	NISP,3		# number of interrupt stack pages
41
42/*
43 * User structure is UPAGES at top of user space.
44 */
45	.globl	_u
46	.set	_u,0x80000000 - UPAGES*NBPG
47
48	.globl	_intstack
49_intstack:
50	.space	NISP*NBPG
51eintstack:
52
53/*
54 * Do a dump.
55 * Called by auto-restart.
56 * May be called manually.
57 */
58	.align	2
59	.globl	_doadump
60	.globl	_msgbufmapped
61_doadump:
62	nop; nop				# .word 0x0101
63#define	_rpbmap	_Sysmap				# rpb, scb, UNIvec[], istack*4
64	bicl2	$PG_PROT,_rpbmap
65	bisl2	$PG_KW,_rpbmap
66	mtpr	$0,$TBIA
67	tstl	_rpb+RP_FLAG			# dump only once!
68	bneq	1f
69	incl	_rpb+RP_FLAG
70	movl	sp,erpb
71	movab	erpb,sp
72	mfpr	$PCBB,-(sp)
73	mfpr	$MAPEN,-(sp)
74	mfpr	$IPL,-(sp)
75	clrl	_msgbufmapped
76	mtpr	$0,$MAPEN
77	mtpr	$HIGH,$IPL
78	pushr	$0x3fff
79	calls	$0,_dumpsys
801:
81	clrl	r11				# boot flags
82	calls	$0,_vaxboot
83	halt
84
85/*
86 * Interrupt vector routines
87 */
88	.globl	_waittime
89
90#define	SCBVEC(name)	.align 2; .globl _X/**/name; _X/**/name
91#define	PANIC(msg)	clrl _waittime; pushab 1f; \
92			calls $1,_panic; 1: .asciz msg
93#define	PRINTF(n,msg)	pushab 1f; calls $n+1,_printf; MSG(msg)
94#define	MSG(msg)	.data; 1: .asciz msg; .text
95#define	PUSHR		pushr $0x3f
96#define	POPR		popr $0x3f
97
98	.data
99nofault: .long	0	# where to go on predicted machcheck
100	.text
101SCBVEC(machcheck):
102	tstl	nofault
103	bneq	1f
104	PUSHR; pushab 6*4(sp); calls $1,_machinecheck; POPR;
105	addl2 (sp)+,sp; rei
106	.align	2
1071:
108	casel	_cpu,$1,$VAX_MAX
1090:
110	.word	8f-0b		# 1 is 780
111	.word	5f-0b		# 2 is 750
112	.word	5f-0b		# 3 is 730
113	.word	7f-0b		# 4 is 8600
114	.word	5f-0b		# 5 is 8200
115	.word	1f-0b		# 6 is 8800 (unsupported)
116	.word	1f-0b		# 7 is 610  (unsupported)
117	.word	1f-0b		# 8 is 630
118	.word	1f-0b		# 9 is ???
119	.word	9f-0b		# 10 is 650
1205:
121#if defined(VAX8200) || defined(VAX750) || defined(VAX730)
122	mtpr	$0xf,$MCESR
123#endif
124	brb	1f
1257:
126#if VAX8600
127	mtpr	$0,$EHSR
128#endif
129	brb	1f
1308:
131#if VAX780
132	mtpr	$0,$SBIFS
133#endif
134	brb	1f
1359:
136#if VAX650
137	bitl	$PG_V,_KA650MERRmap
138	beql	1f	# don't bother clearing err reg if not mapped in
139	movl	$DSER_CLEAR,_ka650merr+4
140#endif
1411:
142	addl2	(sp)+,sp		# discard mchchk trash
143	movl	nofault,(sp)
144	rei
145
146SCBVEC(kspnotval):
147	PANIC("KSP not valid");
148SCBVEC(powfail):
149	halt
150SCBVEC(chme): SCBVEC(chms): SCBVEC(chmu):
151	PANIC("CHM? in kernel");
152
153SCBVEC(nex0zvec):
154	PUSHR
155	clrl	r0
156	brb	1f
157SCBVEC(nex1zvec):
158	PUSHR
159	movl	$1,r0
1601:
161	cmpl	_cpu,$VAX_8600		# this is a frill
162	beql	2f
163	mfpr	$IPL,-(sp)
164	PRINTF(1, "nexus stray intr ipl%x\n")
165	POPR
166	rei
1672:
168	pushl	r0
169	mfpr	$IPL,-(sp)
170	PRINTF(2, "nexus stray intr ipl%x sbia%d\n")
171	POPR
172	rei
173
174SCBVEC(cmrd):
175	PUSHR; calls $0,_memerr; POPR; rei
176
177SCBVEC(wtime):			/* sbi0err on 8600 */
178#if VAX8600
179	cmpl	_cpu,$VAX_8600
180	bneq	wtimo
181	PANIC("sbia0 error")
182wtimo:
183#endif
184	PUSHR; pushl 6*4(sp); PRINTF(1, "write timeout %x\n"); POPR
185	PANIC("wtimo")
186
187SCBVEC(sbi0fail):
188	PANIC("sbia0 fail")
189SCBVEC(sbi0alert):
190#if VAX8200
191	cmpl	_cpu,$VAX_8200
192	bneq	alert
193	PUSHR; calls $0,_rxcdintr; POPR; rei
194alert:
195#endif
196	PANIC("sbia0 alert")
197SCBVEC(sbi0fault):
198	PANIC("sbia0 fault")
199
200#ifdef notyet
201#if VAX8600
202SCBVEC(sbi1fail):
203	PANIC("sbia1 fail")
204SCBVEC(sbi1alert):
205	PANIC("sbia1 alert")
206SCBVEC(sbi1fault):
207	PANIC("sbia1 fault")
208SCBVEC(sbi1err):
209	PANIC("sbia1 error")
210#endif
211#endif
212
213/*
214 * BI 0 bus error (8200), or SBI silo compare error (others)
215 * VMS boot leaves us 1 BI error to ignore.
216 */
217#if VAX8200 && 0
218	.data
219	.align	2
220_ignorebi: .globl _ignorebi
221	.long	1
222	.text
223#endif VAX8200
224
225SCBVEC(sbisilo):
226#if VAX8200
227	cmpl	_cpu,$VAX_8200
228	bneq	sbisilo
229#if 0
230	blbs	_ignorebi,1f
231#else
232	blbs	_cold,1f
233#endif
234	PUSHR; pushl $0; calls $1,_bi_buserr; POPR
2351:
236	rei
237#endif
238sbisilo:
239	PANIC("sbi silo compare error")
240
241/*
242 * SCB stray interrupt catcher.  Compute and print the actual
243 * SCB vector (for fault diagnosis).
244 */
245	.align	2
246_scbstray: .globl _scbstray
247#define	PJ	PUSHR;jsb 1f
248	/* 128 of 'em */
249	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
250	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
251	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
252	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
253	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
254	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
255	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
256	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
257#if VAX8600
258	/* and another 128, for the second SBIA's scb */
259	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
260	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
261	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
262	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
263	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
264	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
265	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
266	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
267#endif
268#undef PJ
2691:
270	subl3	$_scbstray+8,(sp)+,r0
271	mfpr	$IPL,-(sp)
272	ashl	$-1,r0,-(sp)
273/* call a C handler instead? perhaps later */
274	PRINTF(2, "stray scb intr vec 0x%x ipl%x\n")
275	POPR
276	rei
277
278#if NMBA > 0
279SCBVEC(mba3int):
280	PUSHR; incl _intrcnt+I_MBA3; pushl $3; brb 1f
281SCBVEC(mba2int):
282	PUSHR; incl _intrcnt+I_MBA2; pushl $2; brb 1f
283SCBVEC(mba1int):
284	PUSHR; incl _intrcnt+I_MBA1; pushl $1; brb 1f
285SCBVEC(mba0int):
286	PUSHR; incl _intrcnt+I_MBA0; pushl $0
2871:	calls $1,_mbintr
288	POPR
289	incl	_cnt+V_INTR
290	rei
291#endif
292
293#ifdef DW780
294/*
295 * Registers for the uba handling code
296 */
297#define	rUBANUM	r0
298#define	rUBAHD	r1
299#define	rUVEC	r3
300#define	rUBA	r4
301/* r2,r5 are scratch */
302
303#define	I_UBA	I_UBA0		/* base of UBA interrupt counters */
304
305#if NUBA > 4
306SCBVEC(ua7int):
307	PUSHR; movl $7,rUBANUM; moval _uba_hd+(7*UH_SIZE),rUBAHD; brb 1f
308SCBVEC(ua6int):
309	PUSHR; movl $6,rUBANUM; moval _uba_hd+(6*UH_SIZE),rUBAHD; brb 1f
310SCBVEC(ua5int):
311	PUSHR; movl $5,rUBANUM; moval _uba_hd+(5*UH_SIZE),rUBAHD; brb 1f
312SCBVEC(ua4int):
313	PUSHR; movl $4,rUBANUM; moval _uba_hd+(4*UH_SIZE),rUBAHD; brb 1f
314#endif
315SCBVEC(ua3int):
316	PUSHR; movl $3,rUBANUM; moval _uba_hd+(3*UH_SIZE),rUBAHD; brb 1f
317SCBVEC(ua2int):
318	PUSHR; movl $2,rUBANUM; moval _uba_hd+(2*UH_SIZE),rUBAHD; brb 1f
319SCBVEC(ua1int):
320	PUSHR; movl $1,rUBANUM; moval _uba_hd+(1*UH_SIZE),rUBAHD; brb 1f
321SCBVEC(ua0int):
322	PUSHR; movl $0,rUBANUM; moval _uba_hd+(0*UH_SIZE),rUBAHD;
3231:
324	mfpr	$IPL,r2				/* r2 = mfpr(IPL); */
325	movl	UH_UBA(rUBAHD),rUBA		/* uba = uhp->uh_uba; */
326	movl	UBA_BRRVR-0x14*4(rUBA)[r2],rUVEC
327					/* uvec = uba->uba_brrvr[r2-0x14] */
328ubanorm:
329	bleq	ubaerror
330	addl2	UH_VEC(rUBAHD),rUVEC		/* uvec += uh->uh_vec */
331	bicl3	$3,(rUVEC),r1
332	jmp	2(r1)				/* 2 skips ``pushr $0x3f'' */
333ubaerror:
334	PUSHR; calls $0,_ubaerror; POPR		/* ubaerror r/w's r0-r5 */
335	tstl rUVEC; jneq ubanorm		/* rUVEC contains result */
336	incl _intrcnt+I_UBA[rUBANUM]
337	incl	_cnt+V_INTR
338	POPR
339	rei
340#endif
341SCBVEC(cnrint):
342	PUSHR; calls $0,_cnrint; POPR
343	incl _cnt+V_INTR
344	incl _intrcnt+I_CNR
345	rei
346SCBVEC(cnxint):
347	PUSHR; calls $0,_cnxint; POPR
348	incl _cnt+V_INTR
349	incl _intrcnt+I_CNX
350	rei
351SCBVEC(hardclock):
352	PUSHR
353	mtpr $ICCS_RUN|ICCS_IE|ICCS_INT|ICCS_ERR,$ICCS
354#if NPS > 0
355	pushl	4+6*4(sp); pushl 4+6*4(sp);
356	calls	$2,_psextsync
357#endif
358	pushl 4+6*4(sp); pushl 4+6*4(sp);
359	calls $2,_hardclock			# hardclock(pc,psl)
360	POPR;
361	incl	_cnt+V_INTR
362	incl	_intrcnt+I_CLOCK
363	rei
364SCBVEC(softclock):
365	PUSHR
366	pushl	4+6*4(sp); pushl 4+6*4(sp);
367	calls	$2,_softclock			# softclock(pc,psl)
368	POPR;
369	incl	_cnt+V_SOFT
370	rei
371
372#include "../net/netisr.h"
373	.globl	_netisr
374SCBVEC(netintr):
375	PUSHR
376#include "imp.h"
377#if NIMP > 0
378	bbcc	$NETISR_IMP,_netisr,1f; calls $0,_impintr; 1:
379#endif
380#ifdef INET
381	bbcc	$NETISR_IP,_netisr,1f; calls $0,_ipintr; 1:
382#endif
383#ifdef NS
384	bbcc	$NETISR_NS,_netisr,1f; calls $0,_nsintr; 1:
385#endif
386#ifdef ISO
387	bbcc	$NETISR_ISO,_netisr,1f; calls $0,_clnlintr; 1:
388#endif
389	POPR
390	incl	_cnt+V_SOFT
391	rei
392
393SCBVEC(consdin):
394	PUSHR;
395	incl	_intrcnt+I_TUR
396	casel	_cpu,$VAX_750,$VAX_8200
3970:
398	.word	5f-0b		# 2 is VAX_750
399	.word	3f-0b		# 3 is VAX_730
400	.word	6f-0b		# 4 is VAX_8600
401	.word	7f-0b		# 5 is VAX_8200
402	halt
4035:
404#if defined(VAX750) && !defined(MRSP)
405	jsb	tudma
406#endif
4073:
408#if defined(VAX750) || defined(VAX730)
409	calls	$0,_turintr
410	brb	2f
411#else
412	halt
413#endif
4147:
415#if VAX8200
416	calls	$0,_rx50intr
417	brb	2f
418#else
419	halt
420#endif
4216:
422#if VAX8600
423	calls	$0,_crlintr
424#else
425	halt
426#endif
4272:
428	POPR
429	incl	_cnt+V_INTR
430	rei
431
432#if defined(VAX750) || defined(VAX730)
433SCBVEC(consdout):
434	PUSHR; calls $0,_tuxintr; POPR
435	incl _cnt+V_INTR
436	incl _intrcnt+I_TUX
437	rei
438#else
439SCBVEC(consdout):
440	halt
441#endif
442
443#if NDZ > 0
444/*
445 * DZ pseudo dma routine:
446 *	r0 - controller number
447 */
448	.align	1
449	.globl	dzdma
450dzdma:
451	mull2	$8*20,r0
452	movab	_dzpdma(r0),r3		# pdma structure base
453					# for this controller
454dzploop:
455	movl	r3,r0
456	movl	(r0)+,r1		# device register address
457	movzbl	1(r1),r2		# get line number
458	bitb	$0x80,r2		# TRDY on?
459	beql	dzprei			# no
460	bicb2	$0xf8,r2		# clear garbage bits
461	mull2	$20,r2
462	addl2	r2,r0			# point at line's pdma structure
463	movl	(r0)+,r2		# p_mem
464	cmpl	r2,(r0)+		# p_mem < p_end ?
465	bgequ	dzpcall			# no, go call dzxint
466	movb	(r2)+,6(r1)		# dztbuf = *p_mem++
467	movl	r2,-8(r0)
468	brb 	dzploop			# check for another line
469dzprei:
470	POPR
471	incl	_cnt+V_PDMA
472	rei
473
474dzpcall:
475	pushl	r3
476	pushl	(r0)+			# push tty address
477	calls	$1,*(r0)		# call interrupt rtn
478	movl	(sp)+,r3
479	brb 	dzploop			# check for another line
480#endif
481
482#if NUU > 0 && defined(UUDMA)
483/*
484 * Pseudo DMA routine for tu58 (on DL11)
485 *	r0 - controller number
486 */
487	.align	1
488	.globl	uudma
489uudma:
490	movl	_uudinfo[r0],r2
491	movl	16(r2),r2		# r2 = uuaddr
492	mull3	$48,r0,r3
493	movab	_uu_softc(r3),r5	# r5 = uuc
494
495	cvtwl	2(r2),r1		# c = uuaddr->rdb
496	bbc	$15,r1,1f		# if (c & UUDB_ERROR)
497	movl	$13,16(r5)		#	uuc->tu_state = TUC_RCVERR;
498	rsb				#	let uurintr handle it
4991:
500	tstl	4(r5)			# if (uuc->tu_rcnt) {
501	beql	1f
502	movb	r1,*0(r5)		#	*uuc->tu_rbptr++ = r1
503	incl	(r5)
504	decl	4(r5)			#	if (--uuc->tu_rcnt)
505	beql	2f			#		done
506	tstl	(sp)+
507	POPR				# 	registers saved in ubglue.s
508	rei				# }
5092:
510	cmpl	16(r5),$8		# if (uuc->tu_state != TUS_GETH)
511	beql	2f			# 	let uurintr handle it
5121:
513	rsb
5142:
515	mull2	$14,r0			# sizeof(uudata[ctlr]) = 14
516	movab	_uudata(r0),r4		# data = &uudata[ctlr];
517	cmpb	$1,(r4)			# if (data->pk_flag != TUF_DATA)
518	bneq	1b
519#ifdef notdef
520	/* this is for command packets */
521	beql	1f			# 	r0 = uuc->tu_rbptr
522	movl	(r5),r0
523	brb	2f
5241:					# else
525#endif
526	movl	24(r5),r0		# 	r0 = uuc->tu_addr
5272:
528	movzbl	1(r4),r3		# counter to r3 (data->pk_count)
529	movzwl	(r4),r1			# first word of checksum (=header)
530	mfpr	$IPL,-(sp)		# s = spl5();
531	mtpr	$0x15,$IPL		# to keep disk interrupts out
532	clrw	(r2)			# disable receiver interrupts
5333:	bbc	$7,(r2),3b		# while ((uuaddr->rcs & UUCS_READY)==0);
534	cvtwb	2(r2),(r0)+		# *buffer = uuaddr->rdb & 0xff
535	sobgtr	r3,1f			# continue with next byte ...
536	addw2	2(r2),r1		# unless this was the last (odd count)
537	brb	2f
538
5391:	bbc	$7,(r2),1b		# while ((uuaddr->rcs & UUCS_READY)==0);
540	cvtwb	2(r2),(r0)+		# *buffer = uuaddr->rdb & 0xff
541	addw2	-2(r0),r1		# add to checksum..
5422:
543	adwc	$0,r1			# get the carry
544	sobgtr	r3,3b			# loop while r3 > 0
545/*
546 * We're ready to get the checksum
547 */
5481:	bbc	$7,(r2),1b		# while ((uuaddr->rcs & UUCS_READY)==0);
549	cvtwb	2(r2),12(r4)		# get first (lower) byte
5501:	bbc	$7,(r2),1b
551	cvtwb	2(r2),13(r4)		# ..and second
552	cmpw	12(r4),r1		# is checksum ok?
553	beql	1f
554	movl	$14,16(r5)		# uuc->tu_state = TUS_CHKERR
555	brb	2f			# exit
5561:
557	movl	$11,16(r5)		# uuc->tu_state = TUS_GET (ok)
5582:
559	movw	$0x40,(r2)		# enable receiver interrupts
560	mtpr	(sp)+,$IPL		# splx(s);
561	rsb				# continue processing in uurintr
562#endif
563
564#if defined(VAX750) && !defined(MRSP)
565/*
566 * Pseudo DMA routine for VAX-11/750 console tu58
567 *   	    (without MRSP)
568 */
569	.align	1
570	.globl	tudma
571tudma:
572	movab	_tu,r5			# r5 = tu
573	tstl	4(r5)			# if (tu.tu_rcnt) {
574	beql	3f
575	mfpr	$CSRD,r1		# get data from tu58
576	movb	r1,*0(r5)		#	*tu.tu_rbptr++ = r1
577	incl	(r5)
578	decl	4(r5)			#	if (--tu.tu_rcnt)
579	beql	1f			#		done
580	tstl	(sp)+
581	POPR				# 	registers saved in ubglue.s
582	rei				# 	data handled, done
5831:					# }
584	cmpl	16(r5),$8		# if (tu.tu_state != TUS_GETH)
585	beql	2f			# 	let turintr handle it
5863:
587	rsb
5882:
589	movab	_tudata,r4		# r4 = tudata
590	cmpb	$1,(r4)			# if (tudata.pk_flag != TUF_DATA)
591	bneq	3b			# 	let turintr handle it
5921:					# else
593	movl	24(r5),r1		# get buffer pointer to r1
594	movzbl	1(r4),r3		# counter to r3
595	movzwl	(r4),r0			# first word of checksum (=header)
596	mtpr	$0,$CSRS		# disable receiver interrupts
5973:
598	bsbw	5f			# wait for next byte
599	mfpr	$CSRD,r5
600	movb	r5,(r1)+		# *buffer = rdb
601	sobgtr	r3,1f			# continue with next byte ...
602	mfpr	$CSRD,r2		# unless this was the last (odd count)
603	brb	2f
604
6051:	bsbw	5f			# wait for next byte
606	mfpr	$CSRD,r5
607	movb	r5,(r1)+		# *buffer = rdb
608	movzwl	-2(r1),r2		# get the last word back from memory
6092:
610	addw2	r2,r0			# add to checksum..
611	adwc	$0,r0			# get the carry
612	sobgtr	r3,3b			# loop while r3 > 0
613/*
614 * We're ready to get the checksum.
615 */
616	bsbw	5f
617	movab	_tudata,r4
618	mfpr	$CSRD,r5
619	movb	r5,12(r4)		# get first (lower) byte
620	bsbw	5f
621	mfpr	$CSRD,r5
622	movb	r5,13(r4)		# ..and second
623	movab	_tu,r5
624	cmpw	12(r4),r0		# is checksum ok?
625	beql	1f
626	movl	$14,16(r5)		# tu.tu_state = TUS_CHKERR
627	brb	2f			# exit
6281:
629	movl	$11,16(r5)		# tu.tu_state = TUS_GET
6302:
631	mtpr	$0x40,$CSRS		# enable receiver interrupts
632	rsb				# continue processing in turintr
633/*
634 * Loop until a new byte is ready from
635 * the tu58, make sure we don't loop forever
636 */
6375:
638	movl	$5000,r5		# loop max 5000 times
6391:
640	mfpr	$CSRS,r2
641	bbs	$7,r2,1f
642	sobgtr	r5,1b
643	movab	_tu,r5
644	movl	$13,16(r5)		# return TUS_RCVERR
645	tstl	(sp)+			# and let turintr handle it
6461:
647	rsb
648#endif
649
650/*
651 * BI passive release things.
652 */
653SCBVEC(passiverel):
654	rei				# well that was useless
655
656/*
657 * Stray UNIBUS interrupt catch routines
658 */
659	.data
660	.align	2
661#define	PJ	PUSHR;jsb _Xustray
662	.globl	_catcher
663_catcher:
664	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
665	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
666	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
667	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
668	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
669	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
670	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
671	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
672
673	.globl	_cold
674	.globl	_br
675	.globl	_cvec
676_cold:	.long	1
677_br:	.long	0
678_cvec:	.long	0
679
680	.text
681SCBVEC(ustray):
682	blbc	_cold,1f
683	mfpr	$IPL,r11
684	movl	r11,_br
685	subl3	$_catcher+8,(sp)+,r10
686	ashl	$-1,r10,r10
687	movl	r10,_cvec
688	POPR
689	rei
6901:
691	subl3	$_catcher+8,(sp)+,r0
692	ashl	$-1,r0,-(sp)
693	mfpr	$IPL,-(sp)
694	PRINTF(2, "uba?: stray intr ipl %x vec %o\n")
695	POPR
696	rei
697
698#if VAX630 || VAX650
699/*
700 * Emulation OpCode jump table:
701 *	ONLY GOES FROM 0xf8 (-8) TO 0x3B (59)
702 */
703#define EMUTABLE	0x43
704#define NOEMULATE	.long noemulate
705#define	EMULATE(a)	.long _EM/**/a
706	.globl	_emJUMPtable
707_emJUMPtable:
708/* f8 */	EMULATE(ashp);	EMULATE(cvtlp);	NOEMULATE;	NOEMULATE
709/* fc */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
710/* 00 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
711/* 04 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
712/* 08 */	EMULATE(cvtps);	EMULATE(cvtsp);	NOEMULATE;	EMULATE(crc)
713/* 0c */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
714/* 10 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
715/* 14 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
716/* 18 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
717/* 1c */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
718/* 20 */	EMULATE(addp4);	EMULATE(addp6);	EMULATE(subp4);	EMULATE(subp6)
719/* 24 */	EMULATE(cvtpt);	EMULATE(mulp);	EMULATE(cvttp);	EMULATE(divp)
720/* 28 */	NOEMULATE;	EMULATE(cmpc3);	EMULATE(scanc);	EMULATE(spanc)
721/* 2c */	NOEMULATE;	EMULATE(cmpc5);	EMULATE(movtc);	EMULATE(movtuc)
722/* 30 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
723/* 34 */	EMULATE(movp);	EMULATE(cmpp3);	EMULATE(cvtpl);	EMULATE(cmpp4)
724/* 38 */	EMULATE(editpc); EMULATE(matchc); EMULATE(locc); EMULATE(skpc)
725#endif
726
727/*
728 * Trap and fault vector routines
729 */
730#define	TRAP(a)	pushl $T_/**/a; jbr alltraps
731
732/*
733 * Ast delivery (profiling and/or reschedule)
734 */
735SCBVEC(astflt):
736	pushl $0; TRAP(ASTFLT)
737SCBVEC(privinflt):
738	pushl $0; TRAP(PRIVINFLT)
739SCBVEC(xfcflt):
740	pushl $0; TRAP(XFCFLT)
741SCBVEC(resopflt):
742	pushl $0; TRAP(RESOPFLT)
743SCBVEC(resadflt):
744	pushl $0; TRAP(RESADFLT)
745SCBVEC(bptflt):
746	pushl $0; TRAP(BPTFLT)
747SCBVEC(compatflt):
748	TRAP(COMPATFLT);
749SCBVEC(kdbintr):
750	pushl $0; TRAP(KDBTRAP)
751SCBVEC(tracep):
752	pushl $0; TRAP(TRCTRAP)
753SCBVEC(arithtrap):
754	TRAP(ARITHTRAP)
755SCBVEC(protflt):
756	blbs	(sp)+,segflt
757	TRAP(PROTFLT)
758segflt:
759	TRAP(SEGFLT)
760
761/*
762 * The following is called with the stack set up as follows:
763 *
764 *	  (sp):	Opcode
765 *	 4(sp):	Instruction PC
766 *	 8(sp):	Operand 1
767 *	12(sp):	Operand 2
768 *	16(sp):	Operand 3
769 *	20(sp):	Operand 4
770 *	24(sp):	Operand 5
771 *	28(sp):	Operand 6
772 *	32(sp):	Operand 7 (unused)
773 *	36(sp):	Operand 8 (unused)
774 *	40(sp):	Return PC
775 *	44(sp):	Return PSL
776 *	48(sp): TOS before instruction
777 *
778 * Each individual routine is called with the stack set up as follows:
779 *
780 *	  (sp):	Return address of trap handler
781 *	 4(sp):	Opcode (will get return PSL)
782 *	 8(sp):	Instruction PC
783 *	12(sp):	Operand 1
784 *	16(sp):	Operand 2
785 *	20(sp):	Operand 3
786 *	24(sp):	Operand 4
787 *	28(sp):	Operand 5
788 *	32(sp):	Operand 6
789 *	36(sp):	saved register 11
790 *	40(sp):	saved register 10
791 *	44(sp):	Return PC
792 *	48(sp):	Return PSL
793 *	52(sp): TOS before instruction
794 */
795
796SCBVEC(emulate):
797#if VAX630 || VAX650
798	movl	r11,32(sp)		# save register r11 in unused operand
799	movl	r10,36(sp)		# save register r10 in unused operand
800	cvtbl	(sp),r10		# get opcode
801	addl2	$8,r10			# shift negative opcodes
802	subl3	r10,$EMUTABLE,r11	# forget it if opcode is out of range
803	bcs	noemulate
804	movl	_emJUMPtable[r10],r10	# call appropriate emulation routine
805	jsb	(r10)		# routines put return values into regs 0-5
806	movl	32(sp),r11		# restore register r11
807	movl	36(sp),r10		# restore register r10
808	insv	(sp),$0,$4,44(sp)	# and condition codes in Opcode spot
809	addl2	$40,sp			# adjust stack for return
810	rei
811noemulate:
812	addl2	$48,sp			# adjust stack for
813#endif
814	.word	0xffff			# "reserved instruction fault"
815SCBVEC(emulateFPD):
816	.word	0xffff			# "reserved instruction fault"
817SCBVEC(transflt):
818	bitl	$2,(sp)+
819	bnequ	tableflt
820 	jsb	Fastreclaim		# try and avoid pagein
821	TRAP(PAGEFLT)
822tableflt:
823	TRAP(TABLEFLT)
824
825alltraps:
826	mfpr	$USP,-(sp); calls $0,_trap; mtpr (sp)+,$USP
827	incl	_cnt+V_TRAP
828	addl2	$8,sp			# pop type, code
829	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
830	rei
831
832SCBVEC(syscall):
833	pushl	$T_SYSCALL
834	mfpr	$USP,-(sp); calls $0,_syscall; mtpr (sp)+,$USP
835	incl	_cnt+V_SYSCALL
836	addl2	$8,sp			# pop type, code
837	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
838	rei
839
840/*
841 * System page table
842 * Mbmap and Usrptmap are enlarged by CLSIZE entries
843 * as they are managed by resource maps starting with index 1 or CLSIZE.
844 */
845#define	vaddr(x)	((((x)-_Sysmap)/4)*NBPG+0x80000000)
846#define	SYSMAP(mname, vname, npte)			\
847_/**/mname:	.globl	_/**/mname;		\
848	.space	(npte)*4;				\
849	.globl	_/**/vname;			\
850	.set	_/**/vname,vaddr(_/**/mname)
851#define	ADDMAP(npte)	.space	(npte)*4
852
853	.data
854	.align	2
855	SYSMAP(Sysmap	,Sysbase	,SYSPTSIZE	)
856	SYSMAP(Forkmap	,forkutl	,UPAGES		)
857	SYSMAP(Xswapmap	,xswaputl	,UPAGES		)
858	SYSMAP(Xswap2map,xswap2utl	,UPAGES		)
859	SYSMAP(Swapmap	,swaputl	,UPAGES		)
860	SYSMAP(Pushmap	,pushutl	,UPAGES		)
861	SYSMAP(Vfmap	,vfutl		,UPAGES		)
862	SYSMAP(CMAP1	,CADDR1		,1		)
863	SYSMAP(CMAP2	,CADDR2		,1		)
864	SYSMAP(mmap	,vmmap		,1		)
865	SYSMAP(alignmap	,alignutl	,1		)	/* XXX */
866	SYSMAP(msgbufmap,msgbuf		,MSGBUFPTECNT	)
867	SYSMAP(Mbmap	,mbutl		,NMBCLUSTERS*MCLBYTES/NBPG+CLSIZE )
868#ifdef MFS
869#include "../ufs/mfsiom.h"
870	/*
871	 * Used by the mfs_doio() routine for physical I/O
872	 */
873	SYSMAP(Mfsiomap	,mfsiobuf	,MFS_MAPREG )
874#endif /* MFS */
875#ifdef NFS
876#include "../nfs/nfsiom.h"
877	/*
878	 * Used by the nfs_doio() routine for physical I/O
879	 */
880	SYSMAP(Nfsiomap	,nfsiobuf	,NFS_MAPREG )
881#endif /* NFS */
882	/*
883	 * This is the map used by the kernel memory allocator.
884	 * It is expanded as necessary by the special features
885	 * that use it.
886	 *
887	 * XXX: NEED way to compute kmem size from maxusers,
888	 * device complement
889	 */
890	SYSMAP(kmempt	,kmembase	,NKMEMCLUSTERS*CLSIZE )
891#ifdef	SYSVSHM
892				ADDMAP(	SHMMAXPGS	)
893#endif
894#ifdef	GPROF
895				ADDMAP( 600*CLSIZE	)
896#endif
897	SYSMAP(ekmempt	,kmemlimit	,0		)
898
899	SYSMAP(UMBAbeg	,umbabeg	,0		)
900	SYSMAP(Nexmap	,nexus		,16*MAXNNEXUS	)
901#ifdef QBA
902#if (QBAPAGES+UBAIOPAGES) > (UBAPAGES+UBAIOPAGES)*NUBA
903	SYSMAP(UMEMmap	,umem		,(QBAPAGES+UBAIOPAGES) )
904#else
905	SYSMAP(UMEMmap	,umem		,(UBAPAGES+UBAIOPAGES)*NUBA )
906#endif
907#else /* QBA */
908	SYSMAP(UMEMmap	,umem		,(UBAPAGES+UBAIOPAGES)*NUBA )
909#endif /* QBA */
910#if VAX8600
911	SYSMAP(Ioamap	,ioa		,MAXNIOA*IOAMAPSIZ/NBPG	)
912#endif
913#if VAX8200 || VAX630
914	SYSMAP(Clockmap	,ka630clock	,1		)
915#endif
916#if VAX8200
917	/* alas, the clocks on the 8200 and 630 are not quite identical */
918	/* they could be shared for now, but this seemed cleaner */
919	.globl _ka820clock; .set _ka820clock,_ka630clock
920	SYSMAP(Ka820map	,ka820port	,1		)
921	SYSMAP(RX50map	,rx50device	,1		)
922#ifdef notyet
923	SYSMAP(BRAMmap	,ka820bootram	,KA820_BRPAGES	)
924	SYSMAP(EEPROMmap,ka820eeprom	,KA820_EEPAGES	)
925#endif
926#endif
927#if VAX630
928	SYSMAP(Ka630map	,ka630cpu	,1		)
929#endif
930#if VAX650
931 	SYSMAP(KA650MERRmap	,ka650merr	,1		)
932 	SYSMAP(KA650CBDmap	,ka650cbd	,1		)
933 	SYSMAP(KA650SSCmap	,ka650ssc	,3		)
934 	SYSMAP(KA650IPCRmap	,ka650ipcr	,1		)
935 	SYSMAP(KA650CACHEmap	,ka650cache	,KA650_CACHESIZE/NBPG )
936#endif
937#ifdef QBA
938	/*
939	 * qvss and qdss don't coexist - one map will suffice
940	 * for either. qvss is 256K each and qdss is 64K each.
941	 */
942#include "qv.h"
943#include "qd.h"
944#if NQV > 0 || NQD > 0
945	SYSMAP(QVmap	,qvmem		,((512*NQV)+(128*NQD)))
946#endif
947#endif
948	SYSMAP(UMBAend	,umbaend	,0		)
949
950	SYSMAP(Usrptmap	,usrpt		,USRPTSIZE+CLSIZE )
951
952eSysmap:
953	.globl	_Syssize
954	.set	_Syssize,(eSysmap-_Sysmap)/4
955	.text
956
957/*
958 * Initialization
959 *
960 * ipl 0x1f; mapen 0; scbb, pcbb, sbr, slr, isp, ksp not set
961 */
962	.data
963	.globl	_cpu
964_cpu:	.long	0
965	.text
966	.globl	start
967start:
968	.word	0
969	mtpr	$0,$ICCS
970/* set system control block base and system page table params */
971	mtpr	$_scb-0x80000000,$SCBB
972	mtpr	$_Sysmap-0x80000000,$SBR
973	mtpr	$_Syssize,$SLR
974/* double map the kernel into the virtual user addresses of phys mem */
975	mtpr	$_Sysmap,$P0BR
976	mtpr	$_Syssize,$P0LR
977/* set ISP and get cpu type */
978	movl	$_intstack+NISP*NBPG,sp
979	mfpr	$SID,r0
980	movab	_cpu,r1
981	extzv	$24,$8,r0,(r1)
982/* init RPB */
983	movab	_rpb,r0
984	movl	r0,(r0)+			# rp_selfref
985	movab	_doadump,r1
986	movl	r1,(r0)+			# rp_dumprout
987	movl	$0x1f,r2
988	clrl	r3
9891:	addl2	(r1)+,r3; sobgtr r2,1b
990	movl	r3,(r0)+			# rp_chksum
991/* count up memory; _physmem contains limit */
992	clrl	r7
993	ashl	$PGSHIFT,_physmem,r8
994	decl	r8
9951:	pushl	$4; pushl r7; calls $2,_badaddr; tstl r0; bneq 9f
996	acbl	r8,$64*1024,r7,1b
9979:
998#if  VAX630 || VAX650
999/* reserve area at top of memory for processor specific use */
1000	cmpb	_cpu,$VAX_630
1001	beql	1f
1002	cmpb	_cpu,$VAX_650
1003	bneq	2f
1004	subl2	$32768,r7	# space for Qbus map registers
1005	brb	2f
10061:
1007	subl2   $4096,r7	# space for console scratchpad
10082:
1009#endif
1010/* clear memory from kernel bss and pages for proc 0 u. and page table */
1011	movab	_edata,r6; bicl2 $SYSTEM,r6
1012	movab	_end,r5; bicl2 $SYSTEM,r5
1013#ifdef KADB
1014	subl2	$4,r5
10151:	clrl	(r6); acbl r5,$4,r6,1b		# clear just bss
1016	addl2	$4,r5
1017	bbc	$6,r11,0f			# check RB_KDB
1018	bicl3	$SYSTEM,r9,r5			# skip symbol & string tables
1019	bicl3	$SYSTEM,r9,r6			# r9 obtained from boot
1020#endif
10210:	bisl3	$SYSTEM,r5,r9			# convert to virtual address
1022	addl2	$NBPG-1,r9			# roundup to next page
1023	addl2	$(UPAGES*NBPG)+NBPG+NBPG,r5
10241:	clrq	(r6); acbl r5,$8,r6,1b
1025/* trap() and syscall() save r0-r11 in the entry mask (per ../h/reg.h) */
1026/* panic() is convenient place to save all for debugging */
1027	bisw2	$0x0fff,_trap
1028	bisw2	$0x0fff,_syscall
1029	bisw2	$0x0fff,_panic
1030	calls	$0,_fixctlrmask
1031/* initialize system page table: uba vectors and int stack writeable */
1032	clrl	r2
1033	movab	eintstack,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
10341:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
1035/*
1036 * make rpb read-only as red zone for interrupt stack
1037 * (scb(s) and UNIvec are write-protected later)
1038 */
1039	bicl2	$PG_PROT,_rpbmap
1040	bisl2	$PG_KR,_rpbmap
1041/* make kernel text space read-only */
1042	movab	_etext+NBPG-1,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
10431:	bisl3	$PG_V|PG_URKR,r2,_Sysmap[r2]; aoblss r1,r2,1b
1044/* make kernel data, bss, read-write */
1045	bicl3	$SYSTEM,r9,r1; ashl $-PGSHIFT,r1,r1
10461:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
1047/* now go to mapped mode */
1048	mtpr	$0,$TBIA; mtpr $1,$MAPEN; jmp *$0f; 0:
1049/* init mem sizes */
1050	ashl	$-PGSHIFT,r7,_physmem
1051/* setup context for proc[0] == Scheduler */
1052	bicl3	$SYSTEM|(NBPG-1),r9,r6	# make phys, page boundary
1053/* setup page table for proc[0] */
1054	ashl	$-PGSHIFT,r6,r3			# r3 = btoc(r6)
1055	bisl3	$PG_V|PG_KW,r3,_Usrptmap	# init first upt entry
1056	incl	r3
1057	movab	_usrpt,r0
1058	mtpr	r0,$TBIS
1059/* init p0br, p0lr */
1060	mtpr	r0,$P0BR
1061	mtpr	$0,$P0LR
1062/* init p1br, p1lr */
1063	movab	NBPG(r0),r0
1064	movl	$0x200000-UPAGES,r1
1065	mtpr	r1,$P1LR
1066	mnegl	r1,r1
1067	moval	-4*UPAGES(r0)[r1],r2
1068	mtpr	r2,$P1BR
1069/* setup mapping for UPAGES of _u */
1070	movl	$UPAGES,r2; movab _u+NBPG*UPAGES,r1; addl2 $UPAGES,r3; jbr 2f
10711:	decl	r3
1072	moval	-NBPG(r1),r1;
1073	bisl3	$PG_V|PG_URKW,r3,-(r0)
1074	mtpr	r1,$TBIS
10752:	sobgeq	r2,1b
1076/* initialize (slightly) the pcb */
1077	movab	UPAGES*NBPG(r1),PCB_KSP(r1)
1078	mnegl	$1,PCB_ESP(r1)
1079	mnegl	$1,PCB_SSP(r1)
1080	movl	r1,PCB_USP(r1)
1081	mfpr	$P0BR,PCB_P0BR(r1)
1082	mfpr	$P0LR,PCB_P0LR(r1)
1083	movb	$4,PCB_P0LR+3(r1)		# disable ast
1084	mfpr	$P1BR,PCB_P1BR(r1)
1085	mfpr	$P1LR,PCB_P1LR(r1)
1086	movl	$CLSIZE,PCB_SZPT(r1)		# init u.u_pcb.pcb_szpt
1087	movl	r9,PCB_R9(r1)
1088	movl	r10,PCB_R10(r1)
1089	movl	r11,PCB_R11(r1)
1090	movab	1f,PCB_PC(r1)			# initial pc
1091	clrl	PCB_PSL(r1)			# mode(k,k), ipl=0
1092	ashl	$PGSHIFT,r3,r3
1093	mtpr	r3,$PCBB			# first pcbb
1094/* set regs, p0br, p0lr, p1br, p1lr, astlvl, ksp and change to kernel mode */
1095	ldpctx
1096	rei
1097/* put signal trampoline code in u. area */
10981:	movab	_u,r0
1099	movc3	$19,sigcode,PCB_SIGC(r0)
1100/* save boot device in global _bootdev */
1101	movl	r10,_bootdev
1102/* save reboot flags in global _boothowto */
1103	movl	r11,_boothowto
1104#ifdef KADB
1105/* save end of symbol & string table in global _bootesym */
1106	subl3	$NBPG-1,r9,_bootesym
1107#endif
1108/* calculate firstaddr, and call main() */
1109	bicl3	$SYSTEM,r9,r0; ashl $-PGSHIFT,r0,-(sp)
1110	addl2	$UPAGES+1,(sp); calls $1,_main
1111/* proc[1] == /etc/init now running here; run icode */
1112	pushl	$PSL_CURMOD|PSL_PRVMOD; pushl $0; rei
1113
1114/* signal trampoline code: it is known that this code takes exactly 19 bytes */
1115/* in ../vax/pcb.h and in the movc3 above */
1116sigcode:
1117	calls	$4,8(pc)	# params pushed by sendsig
1118	movl	sp,ap		# calls frame built by sendsig
1119	chmk	$SYS_sigreturn	# cleanup mask and onsigstack
1120	halt			# sigreturn() does not return!
1121	.word	0x3f		# registers 0-5
1122	callg	(ap),*16(ap)	# call the signal handler
1123	ret			# return to code above
1124
1125	.globl	_icode
1126	.globl	_initflags
1127	.globl	_szicode
1128/*
1129 * Icode is copied out to process 1 to exec /etc/init.
1130 * If the exec fails, process 1 exits.
1131 */
1132_icode:
1133	pushab	b`argv-l0(pc)
1134l0:	pushab	b`init-l1(pc)
1135l1:	pushl	$2
1136	movl	sp,ap
1137	chmk	$SYS_execv
1138	pushl	r0
1139	chmk	$SYS_exit
1140
1141init:	.asciz	"/sbin/init"
1142	.align	2
1143_initflags:
1144	.long	0
1145argv:	.long	init+6-_icode
1146	.long	_initflags-_icode
1147	.long	0
1148_szicode:
1149	.long	_szicode-_icode
1150
1151/*
1152 * Primitives
1153 */
1154
1155#ifdef GPROF
1156#define	ENTRY(name, regs) \
1157	.globl _/**/name; .align 1; _/**/name: .word regs; jsb mcount
1158#define	JSBENTRY(name, regs) \
1159	.globl _/**/name; _/**/name: \
1160	movl fp,-(sp); movab -12(sp),fp; pushr $(regs); jsb mcount; \
1161	popr $(regs); movl (sp)+,fp
1162#else
1163#define	ENTRY(name, regs) \
1164	.globl _/**/name; .align 1; _/**/name: .word regs
1165#define	JSBENTRY(name, regs) \
1166	.globl _/**/name; _/**/name:
1167#endif GPROF
1168#define R0 0x01
1169#define R1 0x02
1170#define R2 0x04
1171#define R3 0x08
1172#define R4 0x10
1173#define R5 0x20
1174#define R6 0x40
1175
1176/*
1177 * badaddr(addr, len)
1178 *	see if access addr with a len type instruction causes a machine check
1179 *	len is length of access (1=byte, 2=short, 4=long)
1180 */
1181	.globl	_badaddr
1182_badaddr:
1183	.word	0
1184	movl	$1,r0
1185	mfpr	$IPL,r1
1186	mtpr	$HIGH,$IPL
1187	movl	4(ap),r3
1188	movl	8(ap),r4
1189	movab	2f,nofault		# jump to 2f on machcheck
1190	bbc	$0,r4,1f; tstb	(r3)
11911:	bbc	$1,r4,1f; tstw	(r3)
11921:	bbc	$2,r4,1f; tstl	(r3)
11931:	clrl	r0			# made it w/o machine checks
11942:	clrl	nofault
1195	mtpr	r1,$IPL
1196	ret
1197
1198/*
1199 * update profiling information for the user
1200 * addupc(pc, &u.u_prof, ticks)
1201 */
1202ENTRY(addupc, 0)
1203	movl	8(ap),r2		# &u.u_prof
1204	subl3	8(r2),4(ap),r0		# corrected pc
1205	blss	9f
1206	extzv	$1,$31,r0,r0		# logical right shift
1207	extzv	$1,$31,12(r2),r1	# ditto for scale
1208	emul	r1,r0,$0,r0
1209	ashq	$-14,r0,r0
1210	tstl	r1
1211	bneq	9f
1212	bicl2	$1,r0
1213	cmpl	r0,4(r2)		# length
1214	bgequ	9f
1215	addl2	(r2),r0			# base
1216	probew	$3,$2,(r0)
1217	beql	8f
1218	addw2	12(ap),(r0)
12199:
1220	ret
12218:
1222	clrl	12(r2)
1223	ret
1224
1225/*
1226 * Copy a null terminated string from the user address space into
1227 * the kernel address space.
1228 *
1229 * copyinstr(fromaddr, toaddr, maxlength, &lencopied)
1230 */
1231ENTRY(copyinstr, R6)
1232	movl	12(ap),r6		# r6 = max length
1233	jlss	8f
1234	movl	4(ap),r1		# r1 = user address
1235	bicl3	$~(NBPG*CLSIZE-1),r1,r2	# r2 = bytes on first page
1236	subl3	r2,$NBPG*CLSIZE,r2
1237	movl	8(ap),r3		# r3 = kernel address
12381:
1239	cmpl	r6,r2			# r2 = min(bytes on page, length left);
1240	jgeq	2f
1241	movl	r6,r2
12422:
1243	prober	$3,r2,(r1)		# bytes accessible?
1244	jeql	8f
1245	subl2	r2,r6			# update bytes left count
1246#ifdef NOSUBSINST
1247	# fake the locc instr. for processors that don't have it
1248	movl	r2,r0
12496:
1250	tstb	(r1)+
1251	jeql	5f
1252	sobgtr	r0,6b
1253	jbr	7f
12545:
1255	decl	r1
1256	jbr	3f
12577:
1258#else
1259	locc	$0,r2,(r1)		# null byte found?
1260	jneq	3f
1261#endif
1262	subl2	r2,r1			# back up pointer updated by `locc'
1263	movc3	r2,(r1),(r3)		# copy in next piece
1264	movl	$(NBPG*CLSIZE),r2	# check next page
1265	tstl	r6			# run out of space?
1266	jneq	1b
1267	movl	$ENOENT,r0		# set error code and return
1268	jbr	9f
12693:
1270	tstl	16(ap)			# return length?
1271	beql	4f
1272	subl3	r6,12(ap),r6		# actual len = maxlen - unused pages
1273	subl2	r0,r6			#	- unused on this page
1274	addl3	$1,r6,*16(ap)		#	+ the null byte
12754:
1276	subl2	r0,r2			# r2 = number of bytes to move
1277	subl2	r2,r1			# back up pointer updated by `locc'
1278	incl	r2			# copy null byte as well
1279	movc3	r2,(r1),(r3)		# copy in last piece
1280	clrl	r0			# redundant
1281	ret
12828:
1283	movl	$EFAULT,r0
12849:
1285	tstl	16(ap)
1286	beql	1f
1287	subl3	r6,12(ap),*16(ap)
12881:
1289	ret
1290
1291/*
1292 * Copy a null terminated string from the kernel
1293 * address space to the user address space.
1294 *
1295 * copyoutstr(fromaddr, toaddr, maxlength, &lencopied)
1296 */
1297ENTRY(copyoutstr, R6)
1298	movl	12(ap),r6		# r6 = max length
1299	jlss	8b
1300	movl	4(ap),r1		# r1 = kernel address
1301	movl	8(ap),r3		# r3 = user address
1302	bicl3	$~(NBPG*CLSIZE-1),r3,r2	# r2 = bytes on first page
1303	subl3	r2,$NBPG*CLSIZE,r2
13041:
1305	cmpl	r6,r2			# r2 = min(bytes on page, length left);
1306	jgeq	2f
1307	movl	r6,r2
13082:
1309	probew	$3,r2,(r3)		# bytes accessible?
1310	jeql	8b
1311	subl2	r2,r6			# update bytes left count
1312#ifdef NOSUBSINST
1313	# fake the locc instr. for processors that don't have it
1314	movl	r2,r0
13156:
1316	tstb	(r1)+
1317	jeql	5f
1318	sobgtr	r0,6b
1319	jbr	7f
13205:
1321	decl	r1
1322	jbr	3b
13237:
1324#else
1325	locc	$0,r2,(r1)		# null byte found?
1326	jneq	3b
1327#endif
1328	subl2	r2,r1			# back up pointer updated by `locc'
1329	movc3	r2,(r1),(r3)		# copy in next piece
1330	movl	$(NBPG*CLSIZE),r2	# check next page
1331	tstl	r6			# run out of space?
1332	jneq	1b
1333	movl	$ENOENT,r0		# set error code and return
1334	jbr	9b
1335
1336/*
1337 * Copy a null terminated string from one point to another in
1338 * the kernel address space.
1339 *
1340 * copystr(fromaddr, toaddr, maxlength, &lencopied)
1341 */
1342ENTRY(copystr, R6)
1343	movl	12(ap),r6		# r6 = max length
1344	jlss	8b
1345	movl	4(ap),r1		# r1 = src address
1346	movl	8(ap),r3		# r3 = dest address
13471:
1348	movzwl	$65535,r2		# r2 = bytes in first chunk
1349	cmpl	r6,r2			# r2 = min(bytes in chunk, length left);
1350	jgeq	2f
1351	movl	r6,r2
13522:
1353	subl2	r2,r6			# update bytes left count
1354#ifdef NOSUBSINST
1355	# fake the locc instr. for processors that don't have it
1356	movl	r2,r0
13576:
1358	tstb	(r1)+
1359	jeql	5f
1360	sobgtr	r0,6b
1361	jbr	7f
13625:
1363	decl	r1
1364	jbr	3b
13657:
1366#else
1367	locc	$0,r2,(r1)		# null byte found?
1368	jneq	3b
1369#endif
1370	subl2	r2,r1			# back up pointer updated by `locc'
1371	movc3	r2,(r1),(r3)		# copy in next piece
1372	tstl	r6			# run out of space?
1373	jneq	1b
1374	movl	$ENOENT,r0		# set error code and return
1375	jbr	9b
1376
1377/*
1378 * Copy specified amount of data from user space into the kernel
1379 * Copyin(from, to, len)
1380 *	r1 == from (user source address)
1381 *	r3 == to (kernel destination address)
1382 *	r5 == length
1383 */
1384	.align	1
1385JSBENTRY(Copyin, R1|R3|R5)
1386	cmpl	r5,$(NBPG*CLSIZE)	# probing one page or less ?
1387	bgtru	1f			# no
1388	prober	$3,r5,(r1)		# bytes accessible ?
1389	beql	ersb			# no
1390	movc3	r5,(r1),(r3)
1391/*	clrl	r0			# redundant */
1392	rsb
13931:
1394	blss	ersb			# negative length?
1395	pushl	r6			# r6 = length
1396	movl	r5,r6
1397	bicl3	$~(NBPG*CLSIZE-1),r1,r0	# r0 = bytes on first page
1398	subl3	r0,$(NBPG*CLSIZE),r0
1399	addl2	$(NBPG*CLSIZE),r0	# plus one additional full page
1400	jbr	2f
1401
1402ciloop:
1403	movc3	r0,(r1),(r3)
1404	movl	$(2*NBPG*CLSIZE),r0	# next amount to move
14052:
1406	cmpl	r0,r6
1407	bleq	3f
1408	movl	r6,r0
14093:
1410	prober	$3,r0,(r1)		# bytes accessible ?
1411	beql	ersb1			# no
1412	subl2	r0,r6			# last move?
1413	bneq	ciloop			# no
1414
1415	movc3	r0,(r1),(r3)
1416/*	clrl	r0			# redundant */
1417	movl	(sp)+,r6		# restore r6
1418	rsb
1419
1420ersb1:
1421	movl	(sp)+,r6		# restore r6
1422ersb:
1423	movl	$EFAULT,r0
1424	rsb
1425
1426/*
1427 * Copy specified amount of data from kernel to the user space
1428 * Copyout(from, to, len)
1429 *	r1 == from (kernel source address)
1430 *	r3 == to (user destination address)
1431 *	r5 == length
1432 */
1433	.align	1
1434JSBENTRY(Copyout, R1|R3|R5)
1435	cmpl	r5,$(NBPG*CLSIZE)	# moving one page or less ?
1436	bgtru	1f			# no
1437	probew	$3,r5,(r3)		# bytes writeable?
1438	beql	ersb			# no
1439	movc3	r5,(r1),(r3)
1440/*	clrl	r0			# redundant */
1441	rsb
14421:
1443	blss	ersb			# negative length?
1444	pushl	r6			# r6 = length
1445	movl	r5,r6
1446	bicl3	$~(NBPG*CLSIZE-1),r3,r0	# r0 = bytes on first page
1447	subl3	r0,$(NBPG*CLSIZE),r0
1448	addl2	$(NBPG*CLSIZE),r0	# plus one additional full page
1449	jbr	2f
1450
1451coloop:
1452	movc3	r0,(r1),(r3)
1453	movl	$(2*NBPG*CLSIZE),r0	# next amount to move
14542:
1455	cmpl	r0,r6
1456	bleq	3f
1457	movl	r6,r0
14583:
1459	probew	$3,r0,(r3)		# bytes writeable?
1460	beql	ersb1			# no
1461	subl2	r0,r6			# last move?
1462	bneq	coloop			# no
1463
1464	movc3	r0,(r1),(r3)
1465/*	clrl	r0			# redundant */
1466	movl	(sp)+,r6		# restore r6
1467	rsb
1468
1469/*
1470 * savectx is like setjmp but saves all registers.
1471 * Called before swapping out the u. area, restored by resume()
1472 * below.
1473 */
1474#define PCLOC 16	/* location of pc in calls frame */
1475#define APLOC 8		/* location of ap,fp in calls frame */
1476
1477ENTRY(savectx, 0)
1478	movl	4(ap),r0
1479	movq	r6,(r0)+
1480	movq	r8,(r0)+
1481	movq	r10,(r0)+
1482	movq	APLOC(fp),(r0)+	# save ap, fp
1483	addl3	$8,ap,(r0)+	# save sp
1484	movl	PCLOC(fp),(r0)	# save pc
1485	clrl	r0
1486	ret
1487
1488#ifdef KADB
1489/*
1490 * C library -- reset, setexit
1491 *
1492 *	reset(x)
1493 * will generate a "return" from
1494 * the last call to
1495 *	setexit()
1496 * by restoring r6 - r12, ap, fp
1497 * and doing a return.
1498 * The returned value is x; on the original
1499 * call the returned value is 0.
1500 */
1501ENTRY(setexit, 0)
1502	movab	setsav,r0
1503	movq	r6,(r0)+
1504	movq	r8,(r0)+
1505	movq	r10,(r0)+
1506	movq	8(fp),(r0)+		# ap, fp
1507	movab	4(ap),(r0)+		# sp
1508	movl	16(fp),(r0)		# pc
1509	clrl	r0
1510	ret
1511
1512ENTRY(reset, 0)
1513	movl	4(ap),r0	# returned value
1514	movab	setsav,r1
1515	movq	(r1)+,r6
1516	movq	(r1)+,r8
1517	movq	(r1)+,r10
1518	movq	(r1)+,r12
1519	movl	(r1)+,sp
1520	jmp 	*(r1)
1521
1522	.data
1523	.align  2
1524setsav:	.space	10*4
1525	.text
1526#endif
1527
1528	.globl	_whichqs
1529	.globl	_qs
1530	.globl	_cnt
1531
1532	.globl	_noproc
1533	.comm	_noproc,4
1534	.globl	_runrun
1535	.comm	_runrun,4
1536
1537/*
1538 * The following primitives use the fancy VAX instructions
1539 * much like VMS does.  _whichqs tells which of the 32 queues _qs
1540 * have processes in them.  Setrq puts processes into queues, Remrq
1541 * removes them from queues.  The running process is on no queue,
1542 * other processes are on a queue related to p->p_pri, divided by 4
1543 * actually to shrink the 0-127 range of priorities into the 32 available
1544 * queues.
1545 */
1546
1547/*
1548 * Setrq(p), using fancy VAX instructions.
1549 *
1550 * Call should be made at splclock(), and p->p_stat should be SRUN
1551 */
1552	.align	1
1553JSBENTRY(Setrq, R0)
1554	tstl	P_RLINK(r0)		## firewall: p->p_rlink must be 0
1555	beql	set1			##
1556	pushab	set3			##
1557	calls	$1,_panic		##
1558set1:
1559	movzbl	P_PRI(r0),r1		# put on queue which is p->p_pri / 4
1560	ashl	$-2,r1,r1
1561	movaq	_qs[r1],r2
1562	insque	(r0),*4(r2)		# at end of queue
1563	bbss	r1,_whichqs,set2	# mark queue non-empty
1564set2:
1565	rsb
1566
1567set3:	.asciz	"setrq"
1568
1569/*
1570 * Remrq(p), using fancy VAX instructions
1571 *
1572 * Call should be made at splclock().
1573 */
1574	.align	1
1575JSBENTRY(Remrq, R0)
1576	movzbl	P_PRI(r0),r1
1577	ashl	$-2,r1,r1
1578	bbsc	r1,_whichqs,rem1
1579	pushab	rem3			# it wasn't recorded to be on its q
1580	calls	$1,_panic
1581rem1:
1582	remque	(r0),r2
1583	beql	rem2
1584	bbss	r1,_whichqs,rem2
1585rem2:
1586	clrl	P_RLINK(r0)		## for firewall checking
1587	rsb
1588
1589rem3:	.asciz	"remrq"
1590
1591/*
1592 * Masterpaddr is the p->p_addr of the running process on the master
1593 * processor.  When a multiprocessor system, the slave processors will have
1594 * an array of slavepaddr's.
1595 */
1596	.globl	_masterpaddr
1597	.data
1598_masterpaddr:
1599	.long	0
1600
1601	.text
1602sw0:	.asciz	"swtch"
1603
1604/*
1605 * When no processes are on the runq, Swtch branches to idle
1606 * to wait for something to come ready.
1607 */
1608	.globl	Idle
1609Idle: idle:
1610	movl	$1,_noproc
1611	mtpr	$0,$IPL			# must allow interrupts here
16121:
1613	tstl	_whichqs		# look for non-empty queue
1614	bneq	sw1
1615	brb	1b
1616
1617badsw:	pushab	sw0
1618	calls	$1,_panic
1619	/*NOTREACHED*/
1620
1621/*
1622 * Swtch(), using fancy VAX instructions
1623 */
1624	.align	1
1625JSBENTRY(Swtch, 0)
1626	incl	_cnt+V_SWTCH
1627sw1:	ffs	$0,$32,_whichqs,r0	# look for non-empty queue
1628	beql	idle			# if none, idle
1629	mtpr	$0x18,$IPL		# lock out all so _whichqs==_qs
1630	bbcc	r0,_whichqs,sw1		# proc moved via interrupt
1631	movaq	_qs[r0],r1
1632	remque	*(r1),r2		# r2 = p = highest pri process
1633	bvs	badsw			# make sure something was there
1634	beql	sw2
1635	insv	$1,r0,$1,_whichqs	# still more procs in this queue
1636sw2:
1637	clrl	_noproc
1638	clrl	_runrun
1639#ifdef notdef
1640	tstl	P_WCHAN(r2)		## firewalls
1641	bneq	badsw			##
1642	cmpb	P_STAT(r2),$SRUN	##
1643	bneq	badsw			##
1644#endif
1645	clrl	P_RLINK(r2)		##
1646	movl	*P_ADDR(r2),r0
1647#ifdef notdef
1648	cmpl	r0,_masterpaddr		# resume of current proc is easy
1649	beql	res0
1650#endif
1651	movl	r0,_masterpaddr
1652	ashl	$PGSHIFT,r0,r0		# r0 = pcbb(p)
1653/* fall into... */
1654
1655/*
1656 * Resume(pf)
1657 */
1658JSBENTRY(Resume, R0)
1659	mtpr	$HIGH,$IPL			# no interrupts, please
1660	movl	_CMAP2,_u+PCB_CMAP2	# yech
1661	svpctx
1662	mtpr	r0,$PCBB
1663	ldpctx
1664	movl	_u+PCB_CMAP2,_CMAP2	# yech
1665	mtpr	$_CADDR2,$TBIS
1666res0:
1667	tstl	_u+PCB_SSWAP
1668	bneq	res1
1669	rei
1670res1:
1671	movl	_u+PCB_SSWAP,r0		# restore alternate saved context
1672	clrl	_u+PCB_SSWAP
1673	movq	(r0)+,r6			# restore r6, r7
1674	movq	(r0)+,r8			# restore r8, r9
1675	movq	(r0)+,r10			# restore r10, r11
1676	movq	(r0)+,r12			# restore ap, fp
1677	movl	(r0)+,r1			# saved sp
1678	cmpl	r1,sp				# must be a pop
1679	bgequ	1f
1680	pushab	2f
1681	calls	$1,_panic
1682	/* NOTREACHED */
16831:
1684	movl	r1,sp				# restore sp
1685	pushl	$PSL_PRVMOD			# return psl
1686	pushl	(r0)				# address to return to
1687	rei
1688
16892:	.asciz	"ldctx"
1690
1691/*
1692 * {fu,su},{byte,word}, all massaged by asm.sed to jsb's
1693 */
1694	.align	1
1695JSBENTRY(Fuword, R0)
1696	prober	$3,$4,(r0)
1697	beql	fserr
1698	movl	(r0),r0
1699	rsb
1700fserr:
1701	mnegl	$1,r0
1702	rsb
1703
1704	.align	1
1705JSBENTRY(Fubyte, R0)
1706	prober	$3,$1,(r0)
1707	beql	fserr
1708	movzbl	(r0),r0
1709	rsb
1710
1711	.align	1
1712JSBENTRY(Suword, R0|R1)
1713	probew	$3,$4,(r0)
1714	beql	fserr
1715	movl	r1,(r0)
1716	clrl	r0
1717	rsb
1718
1719	.align	1
1720JSBENTRY(Subyte, R0|R1)
1721	probew	$3,$1,(r0)
1722	beql	fserr
1723	movb	r1,(r0)
1724	clrl	r0
1725	rsb
1726
1727/*
1728 * Copy 1 relocation unit (NBPG bytes)
1729 * from user virtual address to physical address
1730 */
1731ENTRY(copyseg, 0)
1732	bisl3	$PG_V|PG_KW,8(ap),_CMAP2
1733	mtpr	$_CADDR2,$TBIS	# invalidate entry for copy
1734	movc3	$NBPG,*4(ap),_CADDR2
1735	ret
1736
1737/*
1738 * zero out physical memory
1739 * specified in relocation units (NBPG bytes)
1740 */
1741ENTRY(clearseg, 0)
1742	bisl3	$PG_V|PG_KW,4(ap),_CMAP1
1743	mtpr	$_CADDR1,$TBIS
1744	movc5	$0,(sp),$0,$NBPG,_CADDR1
1745	ret
1746
1747/*
1748 * Check address.
1749 * Given virtual address, byte count, and rw flag
1750 * returns 0 on no access.
1751 */
1752ENTRY(useracc, 0)
1753	movl	4(ap),r0		# get va
1754	movl	8(ap),r1		# count
1755	tstl	12(ap)			# test for read access ?
1756	bneq	userar			# yes
1757	cmpl	$NBPG,r1			# can we do it in one probe ?
1758	bgeq	uaw2			# yes
1759uaw1:
1760	probew	$3,$NBPG,(r0)
1761	beql	uaerr			# no access
1762	addl2	$NBPG,r0
1763	acbl	$NBPG+1,$-NBPG,r1,uaw1
1764uaw2:
1765	probew	$3,r1,(r0)
1766	beql	uaerr
1767	movl	$1,r0
1768	ret
1769
1770userar:
1771	cmpl	$NBPG,r1
1772	bgeq	uar2
1773uar1:
1774	prober	$3,$NBPG,(r0)
1775	beql	uaerr
1776	addl2	$NBPG,r0
1777	acbl	$NBPG+1,$-NBPG,r1,uar1
1778uar2:
1779	prober	$3,r1,(r0)
1780	beql	uaerr
1781	movl	$1,r0
1782	ret
1783uaerr:
1784	clrl	r0
1785	ret
1786
1787/*
1788 * kernacc - check for kernel access privileges
1789 *
1790 * We can't use the probe instruction directly because
1791 * it ors together current and previous mode.
1792 */
1793 ENTRY(kernacc, 0)
1794	movl	4(ap),r0	# virtual address
1795	bbcc	$31,r0,kacc1
1796	bbs	$30,r0,kacerr
1797	mfpr	$SBR,r2		# address and length of page table (system)
1798	bbss	$31,r2,0f; 0:
1799	mfpr	$SLR,r3
1800	brb	kacc2
1801kacc1:
1802	bbsc	$30,r0,kacc3
1803	mfpr	$P0BR,r2	# user P0
1804	mfpr	$P0LR,r3
1805	brb	kacc2
1806kacc3:
1807	mfpr	$P1BR,r2	# user P1 (stack)
1808	mfpr	$P1LR,r3
1809kacc2:
1810	addl3	8(ap),r0,r1	# ending virtual address
1811	addl2	$NBPG-1,r1
1812	ashl	$-PGSHIFT,r0,r0
1813	ashl	$-PGSHIFT,r1,r1
1814	bbs	$31,4(ap),kacc6
1815	bbc	$30,4(ap),kacc6
1816	cmpl	r0,r3		# user stack
1817	blss	kacerr		# address too low
1818	brb	kacc4
1819kacc6:
1820	cmpl	r1,r3		# compare last page to P0LR or SLR
1821	bgtr	kacerr		# address too high
1822kacc4:
1823	movl	(r2)[r0],r3
1824	bbc	$31,4(ap),kacc4a
1825	bbc	$31,r3,kacerr	# valid bit is off
1826kacc4a:
1827	cmpzv	$27,$4,r3,$1	# check protection code
1828	bleq	kacerr		# no access allowed
1829	tstb	12(ap)
1830	bneq	kacc5		# only check read access
1831	cmpzv	$27,$2,r3,$3	# check low 2 bits of prot code
1832	beql	kacerr		# no write access
1833kacc5:
1834	aoblss	r1,r0,kacc4	# next page
1835	movl	$1,r0		# no errors
1836	ret
1837kacerr:
1838	clrl	r0		# error
1839	ret
1840/*
1841 * Extracted and unrolled most common case of pagein (hopefully):
1842 *	resident and not on free list (reclaim of page is purely
1843 *	for the purpose of simulating a reference bit)
1844 *
1845 * Built in constants:
1846 *	CLSIZE of 2, any bit fields in pte's
1847 */
1848	.text
1849	.globl	Fastreclaim
1850Fastreclaim:
1851	PUSHR
1852#ifdef GPROF
1853	movl	fp,-(sp)
1854	movab	12(sp),fp
1855	jsb	mcount
1856	movl	(sp)+,fp
1857#endif GPROF
1858	extzv	$9,$23,28(sp),r3	# virtual address
1859	bicl2	$1,r3			# v = clbase(btop(virtaddr));
1860	movl	_u+U_PROCP,r5		# p = u.u_procp
1861					# from vtopte(p, v) ...
1862	movl	$1,r2			# type = CTEXT;
1863	cmpl	r3,P_TSIZE(r5)
1864	jlssu	1f			# if (isatsv(p, v)) {
1865	addl3	P_TSIZE(r5),P_DSIZE(r5),r0
1866	cmpl	r3,r0
1867	jgequ	2f
1868	clrl	r2			#	type = !CTEXT;
18691:
1870	ashl	$2,r3,r4
1871	addl2	P_P0BR(r5),r4		#	tptopte(p, vtotp(p, v));
1872	jbr	3f
18732:
1874	cvtwl	P_SZPT(r5),r4		# } else (isassv(p, v)) {
1875	ashl	$7,r4,r4
1876	subl2	$0x400000,r4
1877	addl2	r3,r4
1878	ashl	$2,r4,r4
1879	addl2	P_P0BR(r5),r4		#	sptopte(p, vtosp(p, v));
1880	clrl	r2			# 	type = !CTEXT;
18813:					# }
1882	bitb	$0x82,3(r4)
1883	beql	2f			# if (pte->pg_v || pte->pg_fod)
1884	POPR; rsb			#	let pagein handle it
18852:
1886	bicl3	$0xffe00000,(r4),r0
1887	jneq	2f			# if (pte->pg_pfnum == 0)
1888	POPR; rsb			# 	let pagein handle it
18892:
1890	subl2	_firstfree,r0
1891	ashl	$-1,r0,r0
1892	incl	r0			# pgtocm(pte->pg_pfnum)
1893	mull2	$SZ_CMAP,r0
1894	addl2	_cmap,r0		# &cmap[pgtocm(pte->pg_pfnum)]
1895	tstl	r2
1896	jeql	2f			# if (type == CTEXT &&
1897	jbc	$C_INTRANS,(r0),2f	#     c_intrans)
1898	POPR; rsb			# 	let pagein handle it
18992:
1900	jbc	$C_FREE,(r0),2f		# if (c_free)
1901	POPR; rsb			# 	let pagein handle it
19022:
1903	bisb2	$0x80,3(r4)		# pte->pg_v = 1;
1904	jbc	$26,4(r4),2f		# if (anycl(pte, pg_m)
1905	bisb2	$0x04,3(r4)		#	pte->pg_m = 1;
19062:
1907	bicw3	$0x7f,2(r4),r0
1908	bicw3	$0xff80,6(r4),r1
1909	bisw3	r0,r1,6(r4)		# distcl(pte);
1910	ashl	$PGSHIFT,r3,r0
1911	mtpr	r0,$TBIS
1912	addl2	$NBPG,r0
1913	mtpr	r0,$TBIS		# tbiscl(v);
1914	tstl	r2
1915	jeql	2f			# if (type == CTEXT)
1916	movl	P_TEXTP(r5),r0
1917	movl	X_CADDR(r0),r5		# for (p = p->p_textp->x_caddr; p; ) {
1918	jeql	2f
1919	ashl	$2,r3,r3
19203:
1921	addl3	P_P0BR(r5),r3,r0	#	tpte = tptopte(p, tp);
1922	bisb2	$1,P_FLAG+3(r5)		#	p->p_flag |= SPTECHG;
1923	movl	(r4),(r0)+		#	for (i = 0; i < CLSIZE; i++)
1924	movl	4(r4),(r0)		#		tpte[i] = pte[i];
1925	movl	P_XLINK(r5),r5		#	p = p->p_xlink;
1926	jneq	3b			# }
19272:					# collect a few statistics...
1928	incl	_u+U_RU+RU_MINFLT	# u.u_ru.ru_minflt++;
1929	moval	_cnt,r0
1930	incl	V_FAULTS(r0)		# cnt.v_faults++;
1931	incl	V_PGREC(r0)		# cnt.v_pgrec++;
1932	incl	V_FASTPGREC(r0)		# cnt.v_fastpgrec++;
1933	incl	V_TRAP(r0)		# cnt.v_trap++;
1934	POPR
1935	addl2	$8,sp			# pop pc, code
1936	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
1937	rei
1938