xref: /original-bsd/sys/vax/vax/locore.s (revision 0b685140)
1/*	locore.s	4.62	82/02/18	*/
2
3#include "../h/mtpr.h"
4#include "../h/trap.h"
5#include "../h/psl.h"
6#include "../h/pte.h"
7#include "../h/cpu.h"
8#include "../h/nexus.h"
9#include "../h/ubareg.h"
10#include "../h/cons.h"
11
12#include "dz.h"
13#include "mba.h"
14
15	.set	HIGH,0x1f	# mask for total disable
16	.set	MCKVEC,4	# offset into scb of machine check vector
17	.set	NBPG,512
18	.set	PGSHIFT,9
19
20	.set	NISP,3		# number of interrupt stack pages
21
22/*
23 * User structure is UPAGES at top of user space.
24 */
25	.globl	_u
26	.set	_u,0x80000000 - UPAGES*NBPG
27
28/*
29 * Restart parameter block
30 * This is filled in in machdep.c in startup().
31 * It MUST be page aligned.
32 * When auto-restart occurs, we run restart() in machdep.c, which
33 * takes a core-dump and then cold-starts.
34 */
35	.globl	_rpb
36_rpb:
37	.space	508
38erpb:
39	.space	4
40	.globl	_intstack
41_intstack:
42	.space	NISP*NBPG
43eintstack:
44
45/*
46 * Do a dump.
47 * Called by auto-restart.
48 * May be called manually.
49 */
50	.align	2
51	.globl	_doadump
52_doadump:
53	nop; nop				# .word 0x0101
54#define	_rpbmap	_Sysmap+8			# scb, UNIvec, rpb, istack*4
55	bicl2	$PG_PROT,_rpbmap
56	bisl2	$PG_KW,_rpbmap
57	tstl	_rpb+RP_FLAG			# dump only once!
58	bneq	1f
59	incl	_rpb+RP_FLAG
60	mtpr	$0,$TBIA
61	movl	sp,erpb
62	movab	erpb,sp
63	mfpr	$PCBB,-(sp)
64	mfpr	$MAPEN,-(sp)
65	mfpr	$IPL,-(sp)
66	mtpr	$0,$MAPEN
67	mtpr	$HIGH,$IPL
68	pushr	$0x3fff
69	calls	$0,_dumpsys
701:
71	mfpr	$TXCS,r0
72	bitl	$TXCS_RDY,r0
73	beql	1b
74	mtpr	$TXDB_BOOT,$TXDB
75	halt
76
77/*
78 * Interrupt vector routines
79 */
80	.globl	_waittime
81
82#define	SCBVEC(name)	.align 2; .globl _X/**/name; _X/**/name
83#define	PANIC(msg)	clrl _waittime; pushab 1f; \
84			calls $1,_panic; 1: .asciz msg
85#define	PRINTF(n,msg)	pushab 1f; calls $n+1,_printf; MSG(msg)
86#define	MSG(msg)	.data; 1: .asciz msg; .text
87#define	PUSHR		pushr $0x3f
88#define	POPR		popr $0x3f
89
90SCBVEC(machcheck):
91	PUSHR; pushab 6*4(sp); calls $1,_machinecheck; POPR;
92	addl2 (sp)+,sp; rei
93SCBVEC(kspnotval):
94	PUSHR; PANIC("KSP not valid");
95SCBVEC(powfail):
96	halt
97SCBVEC(chme): SCBVEC(chms): SCBVEC(chmu):
98	PUSHR; PANIC("CHM? in kernel");
99SCBVEC(stray):
100	PUSHR; PRINTF(0, "stray scb interrupt\n"); POPR;
101	rei
102SCBVEC(nexzvec):
103	PUSHR; mfpr $IPL,-(sp); PRINTF(1, "nexus stray intr ipl%x\n"); POPR; rei
104SCBVEC(cmrd):
105	PUSHR; calls $0,_memerr; POPR; rei
106SCBVEC(wtime):
107	PUSHR; pushl 6*4(sp); PRINTF(1,"write timeout %x\n"); POPR;
108	PANIC("wtimo");
109
110#if NMBA > 0
111SCBVEC(mba3int):
112	PUSHR; pushl $3; brb 1f
113SCBVEC(mba2int):
114	PUSHR; pushl $2; brb 1f
115SCBVEC(mba1int):
116	PUSHR; pushl $1; brb 1f
117SCBVEC(mba0int):
118	PUSHR; pushl $0
1191:	calls $1,_mbintr
120	POPR
121	incl	_cnt+V_INTR
122	rei
123#endif
124
125#if VAX780
126/*
127 * Registers for the uba handling code
128 */
129#define	rUBANUM	r0
130#define	rUBAHD	r1
131#define	rUVEC	r3
132#define	rUBA	r4
133/* r2,r5 are scratch */
134
135SCBVEC(ua3int):
136	PUSHR; movl $3,rUBANUM; moval _uba_hd+(3*UH_SIZE),rUBAHD; brb 1f
137SCBVEC(ua2int):
138	PUSHR; movl $2,rUBANUM; moval _uba_hd+(2*UH_SIZE),rUBAHD; brb 1f
139SCBVEC(ua1int):
140	PUSHR; movl $1,rUBANUM; moval _uba_hd+(1*UH_SIZE),rUBAHD; brb 1f
141SCBVEC(ua0int):
142	PUSHR; movl $0,rUBANUM; moval _uba_hd+(0*UH_SIZE),rUBAHD;
1431:
144	incl	_cnt+V_INTR
145	mfpr	$IPL,r2				/* r2 = mfpr(IPL); */
146	movl	UH_UBA(rUBAHD),rUBA		/* uba = uhp->uh_uba; */
147	movl	UBA_BRRVR-0x14*4(rUBA)[r2],rUVEC
148					/* uvec = uba->uba_brrvr[r2-0x14] */
149ubanorm:
150	bleq	ubaerror
151	addl2	UH_VEC(rUBAHD),rUVEC		/* uvec += uh->uh_vec */
152	bicl3	$3,(rUVEC),r1
153	jmp	2(r1)				/* 2 skips ``pushr $0x3f'' */
154ubaerror:
155	PUSHR; calls $0,_ubaerror; POPR		/* ubaerror r/w's r0-r5 */
156	tstl rUVEC; jneq ubanorm		/* rUVEC contains result */
157	POPR
158	rei
159#endif
160SCBVEC(cnrint):
161	PUSHR; calls $0,_cnrint; POPR; incl _cnt+V_INTR; rei
162SCBVEC(cnxint):
163	PUSHR; calls $0,_cnxint; POPR; incl _cnt+V_INTR; rei
164SCBVEC(hardclock):
165	PUSHR
166	pushl 4+6*4(sp); pushl 4+6*4(sp);
167	calls $2,_hardclock			# hardclock(pc,psl)
168	POPR;
169	incl	_cnt+V_INTR		## temp so not to break vmstat -= HZ
170	rei
171SCBVEC(softclock):
172	PUSHR
173	pushl 4+6*4(sp); pushl 4+6*4(sp);
174	calls $2,_softclock			# softclock(pc,psl)
175	POPR;
176	rei
177#ifdef INET
178SCBVEC(ipintr):
179	PUSHR
180	calls $0,_ipintr
181	POPR
182	rei
183SCBVEC(rawintr):
184	PUSHR
185	calls $0,_rawintr
186	POPR
187	rei
188#endif
189#if defined(VAX750) || defined(VAX7ZZ)
190SCBVEC(consdin):
191	PUSHR; calls $0,_turintr; POPR; incl _cnt+V_INTR; rei
192SCBVEC(consdout):
193	PUSHR; calls $0,_tuxintr; POPR; incl _cnt+V_INTR; rei
194#else
195SCBVEC(consdin):
196	halt
197SCBVEC(consdout):
198	halt
199#endif
200
201#if NDZ > 0
202/*
203 * DZ pseudo dma routine:
204 *	r0 - controller number
205 */
206	.align	1
207	.globl	_dzdma
208_dzdma:
209	mull2	$8*20,r0
210	movab	_dzpdma(r0),r3		# pdma structure base
211					# for this controller
212dzploop:
213	movl	r3,r0
214	movl	(r0)+,r1		# device register address
215	movzbl	1(r1),r2		# get line number
216	bitb	$0x80,r2		# TRDY on?
217	beql	dzprei			# no
218	bicb2	$0xf8,r2		# clear garbage bits
219	mull2	$20,r2
220	addl2	r2,r0			# point at line's pdma structure
221	movl	(r0)+,r2		# p_mem
222	cmpl	r2,(r0)+		# p_mem < p_end ?
223	bgequ	dzpcall			# no, go call dzxint
224	movb	(r2)+,6(r1)		# dztbuf = *p_mem++
225	movl	r2,-8(r0)
226	brb 	dzploop			# check for another line
227dzprei:
228	POPR
229	incl	_cnt+V_PDMA
230	rei
231
232dzpcall:
233	pushl	r3
234	pushl	(r0)+			# push tty address
235	calls	$1,*(r0)		# call interrupt rtn
236	movl	(sp)+,r3
237	brb 	dzploop			# check for another line
238#endif
239
240/*
241 * Stray UNIBUS interrupt catch routines
242 */
243	.data
244	.align	2
245#define	PJ	PUSHR;jsb _Xustray
246	.globl	_catcher
247_catcher:
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
257	.globl	_cold
258_cold:	.long	1
259	.data
260
261	.text
262SCBVEC(ustray):
263	blbc	_cold,1f
264	mfpr	$IPL,r11
265	subl3	$_catcher+8,(sp)+,r10
266	ashl	$-1,r10,r10
267	POPR
268	rei
2691:
270	subl3	$_catcher+8,(sp)+,r0
271	ashl	$-1,r0,-(sp)
272	mfpr	$IPL,-(sp)
273	PRINTF(2, "uba?: stray intr ipl %x vec %o\n")
274	POPR
275	rei
276
277/*
278 * Trap and fault vector routines
279 */
280#define	TRAP(a)	pushl $a; brw alltraps
281
282/*
283 * Ast delivery (profiling and/or reschedule)
284 */
285SCBVEC(astflt):
286	pushl $0; TRAP(ASTFLT)
287SCBVEC(privinflt):
288	pushl $0; TRAP(PRIVINFLT)
289SCBVEC(xfcflt):
290	pushl $0; TRAP(XFCFLT)
291SCBVEC(resopflt):
292	pushl $0; TRAP(RESOPFLT)
293SCBVEC(resadflt):
294	pushl $0; TRAP(RESADFLT)
295SCBVEC(bptflt):
296	pushl $0; TRAP(BPTFLT)
297SCBVEC(compatflt):
298	TRAP(COMPATFLT);
299SCBVEC(tracep):
300	pushl $0; TRAP(TRCTRAP)
301SCBVEC(arithtrap):
302	TRAP(ARITHTRAP)
303SCBVEC(protflt):
304	blbs	(sp)+,segflt
305	TRAP(PROTFLT)
306segflt:
307	TRAP(SEGFLT)
308SCBVEC(transflt):
309	bitl	$2,(sp)+
310	bnequ	tableflt
311	TRAP(PAGEFLT)
312tableflt:
313	TRAP(TABLEFLT)
314
315alltraps:
316	mfpr	$USP,-(sp); calls $0,_trap; mtpr (sp)+,$USP
317	incl	_cnt+V_TRAP
318	addl2	$8,sp			# pop type, code
319	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
320	rei
321
322SCBVEC(syscall):
323	pushl	$SYSCALL
324	mfpr	$USP,-(sp); calls $0,_syscall; mtpr (sp)+,$USP
325	incl	_cnt+V_SYSCALL
326	addl2	$8,sp			# pop type, code
327	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
328	rei
329
330/*
331 * System page table
332 */
333#define	vaddr(x)	((((x)-_Sysmap)/4)*NBPG+0x80000000)
334#define	SYSMAP(mname, vname, npte)			\
335_/**/mname:	.globl	_/**/mname;		\
336	.space	npte*4;				\
337	.globl	_/**/vname;			\
338	.set	_/**/vname,vaddr(_/**/mname)
339
340	.data
341	.align	2
342	SYSMAP(Sysmap	,Sysbase	,SYSPTSIZE	)
343	SYSMAP(UMBAbeg	,umbabeg	,0		)
344	SYSMAP(Nexmap	,nexus		,16*MAXNNEXUS	)
345	SYSMAP(UMEMmap	,umem		,16*MAXNUBA	)
346	SYSMAP(UMBAend	,umbaend	,0		)
347	SYSMAP(Usrptmap	,usrpt		,USRPTSIZE	)
348	SYSMAP(Forkmap	,forkutl	,UPAGES		)
349	SYSMAP(Xswapmap	,xswaputl	,UPAGES		)
350	SYSMAP(Xswap2map,xswap2utl	,UPAGES		)
351	SYSMAP(Swapmap	,swaputl	,UPAGES		)
352	SYSMAP(Pushmap	,pushutl	,UPAGES		)
353	SYSMAP(Vfmap	,vfutl		,UPAGES		)
354	SYSMAP(CMAP1	,CADDR1		,1		)
355	SYSMAP(CMAP2	,CADDR2		,1		)
356	SYSMAP(mcrmap	,mcr		,1		)
357	SYSMAP(mmap	,vmmap		,1		)
358	SYSMAP(msgbufmap,msgbuf		,MSGBUFPTECNT	)
359	SYSMAP(camap	,cabase		,16*CLSIZE	)
360	SYSMAP(ecamap	,calimit	,0		)
361	SYSMAP(Mbmap	,mbutl		,NMBCLUSTERS*CLSIZE)
362
363eSysmap:
364	.globl	_Syssize
365	.set	_Syssize,(eSysmap-_Sysmap)/4
366	.text
367
368/*
369 * Initialization
370 *
371 * ipl 0x1f; mapen 0; scbb, pcbb, sbr, slr, isp, ksp not set
372 */
373	.data
374	.globl	_cpu
375_cpu:	.long	0
376	.text
377	.globl	start
378start:
379	.word	0
380/* set system control block base and system page table params */
381	mtpr	$_scb-0x80000000,$SCBB
382	mtpr	$_Sysmap-0x80000000,$SBR
383	mtpr	$_Syssize,$SLR
384/* double map the kernel into the virtual user addresses of phys mem */
385	mtpr	$_Sysmap,$P0BR
386	mtpr	$_Syssize,$P0LR
387/* set ISP and get cpu type */
388	movl	$_intstack+NISP*NBPG,sp
389	mfpr	$SID,r0
390	movab	_cpu,r1
391	extzv	$24,$8,r0,(r1)
392/* init RPB */
393	movab	_rpb,r0
394	movl	r0,(r0)+			# rp_selfref
395	movab	_doadump,r1
396	movl	r1,(r0)+			# rp_dumprout
397	movl	$0x1f,r2
398	clrl	r3
3991:	addl2	(r1)+,r3; sobgtr r2,1b
400	movl	r3,(r0)+			# rp_chksum
401/* count up memory */
402	clrl	r7
4031:	pushl	$4; pushl r7; calls $2,_badaddr; tstl r0; bneq 9f
404	acbl	$8192*1024-1,$64*1024,r7,1b
4059:
406/* clear memory from kernel bss and pages for proc 0 u. and page table */
407	movab	_edata,r6
408	movab	_end,r5
409	bbcc	$31,r5,0f; 0:
410	addl2	$(UPAGES*NBPG)+NBPG+NBPG,r5
4111:	clrq	(r6); acbl r5,$8,r6,1b
412/* trap() and syscall() save r0-r11 in the entry mask (per ../h/reg.h) */
413	bisw2	$0x0fff,_trap
414	bisw2	$0x0fff,_syscall
415	calls	$0,_fixctlrmask
416/* initialize system page table: scb and int stack writeable */
417	clrl	r2
418	movab	eintstack,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
4191:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
420/* make rpb read-only as red zone for interrupt stack */
421	bicl2	$PG_PROT,_rpbmap
422	bisl2	$PG_KR,_rpbmap
423/* make kernel text space read-only */
424	movab	_etext+NBPG-1,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
4251:	bisl3	$PG_V|PG_KR,r2,_Sysmap[r2]; aoblss r1,r2,1b
426/* make kernel data, bss, read-write */
427	movab	_end+NBPG-1,r1; bbcc $31,r1,0f; 0:; ashl $-PGSHIFT,r1,r1
4281:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
429/* now go to mapped mode */
430	mtpr	$1,$TBIA; mtpr $1,$MAPEN; jmp *$0f; 0:
431/* init mem sizes */
432	ashl	$-PGSHIFT,r7,_maxmem
433	movl	_maxmem,_physmem
434	movl	_maxmem,_freemem
435/* setup context for proc[0] == Scheduler */
436	movab	_end+NBPG-1,r6
437	bicl2	$NBPG-1,r6		# make page boundary
438/* setup page table for proc[0] */
439	bbcc	$31,r6,0f; 0:
440	ashl	$-PGSHIFT,r6,r3			# r3 = btoc(r6)
441	bisl3	$PG_V|PG_KW,r3,_Usrptmap	# init first upt entry
442	incl	r3
443	movab	_usrpt,r0
444	mtpr	r0,$TBIS
445/* init p0br, p0lr */
446	mtpr	r0,$P0BR
447	mtpr	$0,$P0LR
448/* init p1br, p1lr */
449	movab	NBPG(r0),r0
450	movl	$0x200000-UPAGES,r1
451	mtpr	r1,$P1LR
452	mnegl	r1,r1
453	moval	-4*UPAGES(r0)[r1],r2
454	mtpr	r2,$P1BR
455/* setup mapping for UPAGES of _u */
456	movl	$UPAGES,r2; movab _u+NBPG*UPAGES,r1; addl2 $UPAGES,r3; jbr 2f
4571:	decl	r3
458	moval	-NBPG(r1),r1;
459	bisl3	$PG_V|PG_URKW,r3,-(r0)
460	mtpr	r1,$TBIS
4612:	sobgeq	r2,1b
462/* initialize (slightly) the pcb */
463	movab	UPAGES*NBPG(r1),PCB_KSP(r1)
464	mnegl	$1,PCB_ESP(r1)
465	mnegl	$1,PCB_SSP(r1)
466	movl	r1,PCB_USP(r1)
467	mfpr	$P0BR,PCB_P0BR(r1)
468	mfpr	$P0LR,PCB_P0LR(r1)
469	movb	$4,PCB_P0LR+3(r1)		# disable ast
470	mfpr	$P1BR,PCB_P1BR(r1)
471	mfpr	$P1LR,PCB_P1LR(r1)
472	movl	$CLSIZE,PCB_SZPT(r1)		# init u.u_pcb.pcb_szpt
473	movl	r11,PCB_R11(r1)
474	movab	1f,PCB_PC(r1)			# initial pc
475	clrl	PCB_PSL(r1)			# mode(k,k), ipl=0
476	ashl	$PGSHIFT,r3,r3
477	mtpr	r3,$PCBB			# first pcbb
478/* set regs, p0br, p0lr, p1br, p1lr, astlvl, ksp and change to kernel mode */
479	ldpctx
480	rei
481/* put signal trampoline code in u. area */
4821:	movab	_u,r0
483	movc3	$12,sigcode,PCB_SIGC(r0)
484/* save reboot flags in global _boothowto */
485	movl	r11,_boothowto
486/* calculate firstaddr, and call main() */
487	movab	_end+NBPG-1,r0; bbcc $31,r0,0f; 0:; ashl $-PGSHIFT,r0,-(sp)
488	addl2	$UPAGES+1,(sp); calls $1,_main
489/* proc[1] == /etc/init now running here; run icode */
490	pushl	$PSL_CURMOD|PSL_PRVMOD; pushl $0; rei
491
492/* signal trampoline code: it is known that this code takes exactly 12 bytes */
493/* in ../h/pcb.h and in the movc3 above */
494sigcode:
495	calls	$3,1(pc)
496	rei
497	.word	0x7f				# registers 0-6 (6==sp/compat)
498	callg	(ap),*12(ap)
499	ret
500
501/*
502 * Primitives
503 */
504
505/*
506 * badaddr(addr, len)
507 *	see if access addr with a len type instruction causes a machine check
508 *	len is length of access (1=byte, 2=short, 4=long)
509 */
510	.globl	_badaddr
511_badaddr:
512	.word	0
513	movl	$1,r0
514	mfpr	$IPL,r1
515	mtpr	$HIGH,$IPL
516	movl	_scb+MCKVEC,r2
517	movl	4(ap),r3
518	movl	8(ap),r4
519	movab	9f+INTSTK,_scb+MCKVEC
520	bbc	$0,r4,1f; tstb	(r3)
5211:	bbc	$1,r4,1f; tstw	(r3)
5221:	bbc	$2,r4,1f; tstl	(r3)
5231:	clrl	r0			# made it w/o machine checks
5242:	movl	r2,_scb+MCKVEC
525	mtpr	r1,$IPL
526	ret
527	.align	2
5289:
529	casel	_cpu,$1,$VAX_MAX
5300:
531	.word	8f-0b		# 1 is 780
532	.word	5f-0b		# 2 is 750
533	.word	5f-0b		# 3 is 7ZZ
5345:
535#if defined(VAX750) || defined(VAX7ZZ)
536	mtpr	$0xf,$MCESR
537#endif
538	brb	1f
5398:
540#if VAX780
541	mtpr	$0,$SBIFS
542#endif
5431:
544	addl2	(sp)+,sp		# discard mchchk trash
545	movab	2b,(sp)
546	rei
547
548_addupc:	.globl	_addupc
549	.word	0x0
550	movl	8(ap),r2		# &u.u_prof
551	subl3	8(r2),4(ap),r0		# corrected pc
552	blss	9f
553	extzv	$1,$31,r0,r0		# logical right shift
554	extzv	$1,$31,12(r2),r1	# ditto for scale
555	emul	r1,r0,$0,r0
556	ashq	$-14,r0,r0
557	tstl	r1
558	bneq	9f
559	incl	r0
560	bicl2	$1,r0
561	cmpl	r0,4(r2)		# length
562	bgequ	9f
563	addl2	(r2),r0			# base
564	probew	$3,$2,(r0)
565	beql	8f
566	addw2	12(ap),(r0)
5679:
568	ret
5698:
570	clrl	12(r2)
571	ret
572
573_Copyin:	.globl	_Copyin		# <<<massaged for jsb by asm.sed>>>
574	movl	12(sp),r0		# copy length
575	blss	ersb
576	movl	4(sp),r1		# copy user address
577	cmpl	$NBPG,r0		# probing one page or less ?
578	bgeq	cishort			# yes
579ciloop:
580	prober	$3,$NBPG,(r1)		# bytes accessible ?
581	beql	ersb			# no
582	addl2	$NBPG,r1		# incr user address ptr
583	acbl	$NBPG+1,$-NBPG,r0,ciloop	# reduce count and loop
584cishort:
585	prober	$3,r0,(r1)		# bytes accessible ?
586	beql	ersb			# no
587	movc3	12(sp),*4(sp),*8(sp)
588	clrl	r0
589	rsb
590
591ersb:
592	mnegl	$1,r0
593	rsb
594
595_Copyout: 	.globl	_Copyout	# <<<massaged for jsb by asm.sed >>>
596	movl	12(sp),r0		# get count
597	blss	ersb
598	movl	8(sp),r1		# get user address
599	cmpl	$NBPG,r0		# can do in one probew?
600	bgeq	coshort			# yes
601coloop:
602	probew	$3,$NBPG,(r1)		# bytes accessible?
603	beql	ersb			# no
604	addl2	$NBPG,r1		# increment user address
605	acbl	$NBPG+1,$-NBPG,r0,coloop	# reduce count and loop
606coshort:
607	probew	$3,r0,(r1)		# bytes accessible?
608	beql	ersb			# no
609	movc3	12(sp),*4(sp),*8(sp)
610	clrl	r0
611	rsb
612
613/*
614 * non-local goto's
615 */
616	.globl	_Setjmp
617_Setjmp:
618	movq	r6,(r0)+
619	movq	r8,(r0)+
620	movq	r10,(r0)+
621	movq	r12,(r0)+
622	addl3	$4,sp,(r0)+
623	movl	(sp),(r0)
624	clrl	r0
625	rsb
626
627	.globl	_Longjmp
628_Longjmp:
629	movq	(r0)+,r6
630	movq	(r0)+,r8
631	movq	(r0)+,r10
632	movq	(r0)+,r12
633	movl	(r0)+,r1
634	cmpl	r1,sp				# must be a pop
635	bgequ	lj2
636	pushab	lj1
637	calls	$1,_panic
638lj2:
639	movl	r1,sp
640	jmp	*(r0)				# ``rsb''
641
642lj1:	.asciz	"longjmp"
643
644	.globl	_whichqs
645	.globl	_qs
646	.globl	_cnt
647
648	.globl	_noproc
649	.comm	_noproc,4
650	.globl	_runrun
651	.comm	_runrun,4
652
653/*
654 * The following primitives use the fancy VAX instructions
655 * much like VMS does.  _whichqs tells which of the 32 queues _qs
656 * have processes in them.  Setrq puts processes into queues, Remrq
657 * removes them from queues.  The running process is on no queue,
658 * other processes are on a queue related to p->p_pri, divided by 4
659 * actually to shrink the 0-127 range of priorities into the 32 available
660 * queues.
661 */
662
663/*
664 * Setrq(p), using fancy VAX instructions.
665 *
666 * Call should be made at spl6(), and p->p_stat should be SRUN
667 */
668	.globl	_Setrq		# <<<massaged to jsb by "asm.sed">>>
669_Setrq:
670	tstl	P_RLINK(r0)		## firewall: p->p_rlink must be 0
671	beql	set1			##
672	pushab	set3			##
673	calls	$1,_panic		##
674set1:
675	movzbl	P_PRI(r0),r1		# put on queue which is p->p_pri / 4
676	ashl	$-2,r1,r1
677	movaq	_qs[r1],r2
678	insque	(r0),*4(r2)		# at end of queue
679	bbss	r1,_whichqs,set2	# mark queue non-empty
680set2:
681	rsb
682
683set3:	.asciz	"setrq"
684
685/*
686 * Remrq(p), using fancy VAX instructions
687 *
688 * Call should be made at spl6().
689 */
690	.globl	_Remrq		# <<<massaged to jsb by "asm.sed">>>
691_Remrq:
692	movzbl	P_PRI(r0),r1
693	ashl	$-2,r1,r1
694	bbsc	r1,_whichqs,rem1
695	pushab	rem3			# it wasn't recorded to be on its q
696	calls	$1,_panic
697rem1:
698	remque	(r0),r2
699	beql	rem2
700	bbss	r1,_whichqs,rem2
701rem2:
702	clrl	P_RLINK(r0)		## for firewall checking
703	rsb
704
705rem3:	.asciz	"remrq"
706
707/*
708 * Masterpaddr is the p->p_addr of the running process on the master
709 * processor.  When a multiprocessor system, the slave processors will have
710 * an array of slavepaddr's.
711 */
712	.globl	_masterpaddr
713	.data
714_masterpaddr:
715	.long	0
716
717	.text
718sw0:	.asciz	"swtch"
719/*
720 * Swtch(), using fancy VAX instructions
721 */
722	.globl	_Swtch
723_Swtch:				# <<<massaged to jsb by "asm.sed">>>
724	movl	$1,_noproc
725	clrl	_runrun
726sw1:	ffs	$0,$32,_whichqs,r0	# look for non-empty queue
727	bneq	sw1a
728	mtpr	$0,$IPL			# must allow interrupts here
729	brw	sw1			# this is an idle loop!
730sw1a:	mtpr	$0x18,$IPL		# lock out all so _whichqs==_qs
731	bbcc	r0,_whichqs,sw1		# proc moved via lbolt interrupt
732	movaq	_qs[r0],r1
733	remque	*(r1),r2		# r2 = p = highest pri process
734	bvc	sw2			# make sure something was there
735sw1b:	pushab	sw0
736	calls	$1,_panic
737sw2:	beql	sw3
738	insv	$1,r0,$1,_whichqs	# still more procs in this queue
739sw3:
740	clrl	_noproc
741	tstl	P_WCHAN(r2)		## firewalls
742	bneq	sw1b			##
743	movzbl	P_STAT(r2),r3		##
744	cmpl	$SRUN,r3		##
745	bneq	sw1b			##
746	clrl	P_RLINK(r2)		##
747	movl	*P_ADDR(r2),r0
748	movl	r0,_masterpaddr
749	ashl	$PGSHIFT,r0,r0		# r0 = pcbb(p)
750/*	mfpr	$PCBB,r1		# resume of current proc is easy
751 *	cmpl	r0,r1
752 */	beql	res0
753	incl	_cnt+V_SWTCH
754/* fall into... */
755
756/*
757 * Resume(pf)
758 */
759	.globl	_Resume		# <<<massaged to jsb by "asm.sed">>>
760_Resume:
761	mtpr	$0x18,$IPL			# no interrupts, please
762	movl	_CMAP2,_u+PCB_CMAP2	# yech
763	svpctx
764	mtpr	r0,$PCBB
765	ldpctx
766	movl	_u+PCB_CMAP2,_CMAP2	# yech
767	mtpr	$_CADDR2,$TBIS
768res0:
769	tstl	_u+PCB_SSWAP
770	beql	res1
771	movl	_u+PCB_SSWAP,r0
772	clrl	_u+PCB_SSWAP
773	movab	_Longjmp,(sp)
774	movl	$PSL_PRVMOD,4(sp)		# ``cheating'' (jfr)
775res1:
776	rei
777
778/*
779 * {fu,su},{byte,word}, all massaged by asm.sed to jsb's
780 */
781	.globl	_Fuword
782_Fuword:
783	prober	$3,$4,(r0)
784	beql	fserr
785	movl	(r0),r0
786	rsb
787fserr:
788	mnegl	$1,r0
789	rsb
790
791	.globl	_Fubyte
792_Fubyte:
793	prober	$3,$1,(r0)
794	beql	fserr
795	movzbl	(r0),r0
796	rsb
797
798	.globl	_Suword
799_Suword:
800	probew	$3,$4,(r0)
801	beql	fserr
802	movl	r1,(r0)
803	clrl	r0
804	rsb
805
806	.globl	_Subyte
807_Subyte:
808	probew	$3,$1,(r0)
809	beql	fserr
810	movb	r1,(r0)
811	clrl	r0
812	rsb
813
814/*
815 * Copy 1 relocation unit (NBPG bytes)
816 * from user virtual address to physical address
817 */
818_copyseg: 	.globl	_copyseg
819	.word	0x0
820	bisl3	$PG_V|PG_KW,8(ap),_CMAP2
821	mtpr	$_CADDR2,$TBIS	# invalidate entry for copy
822	movc3	$NBPG,*4(ap),_CADDR2
823	ret
824
825/*
826 * zero out physical memory
827 * specified in relocation units (NBPG bytes)
828 */
829_clearseg: 	.globl	_clearseg
830	.word	0x0
831	bisl3	$PG_V|PG_KW,4(ap),_CMAP1
832	mtpr	$_CADDR1,$TBIS
833	movc5	$0,(sp),$0,$NBPG,_CADDR1
834	ret
835
836/*
837 * Check address.
838 * Given virtual address, byte count, and rw flag
839 * returns 0 on no access.
840 */
841_useracc:	.globl	_useracc
842	.word	0x0
843	movl	4(ap),r0		# get va
844	movl	8(ap),r1		# count
845	tstl	12(ap)			# test for read access ?
846	bneq	userar			# yes
847	cmpl	$NBPG,r1			# can we do it in one probe ?
848	bgeq	uaw2			# yes
849uaw1:
850	probew	$3,$NBPG,(r0)
851	beql	uaerr			# no access
852	addl2	$NBPG,r0
853	acbl	$NBPG+1,$-NBPG,r1,uaw1
854uaw2:
855	probew	$3,r1,(r0)
856	beql	uaerr
857	movl	$1,r0
858	ret
859
860userar:
861	cmpl	$NBPG,r1
862	bgeq	uar2
863uar1:
864	prober	$3,$NBPG,(r0)
865	beql	uaerr
866	addl2	$NBPG,r0
867	acbl	$NBPG+1,$-NBPG,r1,uar1
868uar2:
869	prober	$3,r1,(r0)
870	beql	uaerr
871	movl	$1,r0
872	ret
873uaerr:
874	clrl	r0
875	ret
876
877/*
878 * kernacc - check for kernel access privileges
879 *
880 * We can't use the probe instruction directly because
881 * it ors together current and previous mode.
882 */
883	.globl	_kernacc
884_kernacc:
885	.word	0x0
886	movl	4(ap),r0	# virtual address
887	bbcc	$31,r0,kacc1
888	bbs	$30,r0,kacerr
889	mfpr	$SBR,r2		# address and length of page table (system)
890	bbss	$31,r2,0f; 0:
891	mfpr	$SLR,r3
892	brb	kacc2
893kacc1:
894	bbsc	$30,r0,kacc3
895	mfpr	$P0BR,r2	# user P0
896	mfpr	$P0LR,r3
897	brb	kacc2
898kacc3:
899	mfpr	$P1BR,r2	# user P1 (stack)
900	mfpr	$P1LR,r3
901kacc2:
902	addl3	8(ap),r0,r1	# ending virtual address
903	addl2	$NBPG-1,r1
904	ashl	$-PGSHIFT,r0,r0
905	ashl	$-PGSHIFT,r1,r1
906	bbs	$31,4(ap),kacc6
907	bbc	$30,4(ap),kacc6
908	cmpl	r0,r3		# user stack
909	blss	kacerr		# address too low
910	brb	kacc4
911kacc6:
912	cmpl	r1,r3		# compare last page to P0LR or SLR
913	bgtr	kacerr		# address too high
914kacc4:
915	movl	(r2)[r0],r3
916	bbc	$31,4(ap),kacc4a
917	bbc	$31,r3,kacerr	# valid bit is off
918kacc4a:
919	cmpzv	$27,$4,r3,$1	# check protection code
920	bleq	kacerr		# no access allowed
921	tstb	12(ap)
922	bneq	kacc5		# only check read access
923	cmpzv	$27,$2,r3,$3	# check low 2 bits of prot code
924	beql	kacerr		# no write access
925kacc5:
926	aoblss	r1,r0,kacc4	# next page
927	movl	$1,r0		# no errors
928	ret
929kacerr:
930	clrl	r0		# error
931	ret
932