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