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