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