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