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