xref: /original-bsd/sys/vax/vax/locore.s (revision 62734ea8)
1/*	locore.s	4.73	82/11/03	*/
2
3#include "../vax/mtpr.h"
4#include "../vax/trap.h"
5#include "../h/psl.h"
6#include "../h/pte.h"
7#include "../vax/cpu.h"
8#include "../vax/nexus.h"
9#include "../vaxuba/ubareg.h"
10#include "../vax/cons.h"
11#include "../vax/clock.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	mtpr $ICCS_RUN|ICCS_IE|ICCS_INT|ICCS_ERR,$ICCS
168	pushl 4+6*4(sp); pushl 4+6*4(sp);
169	calls $2,_hardclock			# hardclock(pc,psl)
170#if NPS > 0
171	pushl	4+6*4(sp); pushl 4+6*4(sp);
172	calls	$2,_psextsync
173#endif
174	POPR;
175	incl	_cnt+V_INTR		## temp so not to break vmstat -= HZ
176	rei
177SCBVEC(softclock):
178	PUSHR
179#if NDZ > 0
180	calls	$0,_dztimer
181#endif
182#if NDH > 0
183	calls	$0,_dhtimer
184#endif
185	pushl	4+6*4(sp); pushl 4+6*4(sp);
186	calls	$2,_softclock			# softclock(pc,psl)
187	POPR;
188	rei
189#include "../net/netisr.h"
190	.globl	_netisr
191SCBVEC(netintr):
192	PUSHR
193	bbcc	$NETISR_RAW,_netisr,1f; calls $0,_rawintr; 1:
194#ifdef INET
195#include "../netinet/in_systm.h"
196	bbcc	$NETISR_IP,_netisr,1f; calls $0,_ipintr; 1:
197#endif
198#ifdef NS
199	bbcc	$NETISR_NS,_netisr,1f; calls $0,_nsintr; 1:
200#endif
201	POPR
202	rei
203#if defined(VAX750) || defined(VAX730)
204SCBVEC(consdin):
205	PUSHR; calls $0,_turintr; POPR; incl _cnt+V_INTR; rei
206SCBVEC(consdout):
207	PUSHR; calls $0,_tuxintr; POPR; incl _cnt+V_INTR; rei
208#else
209SCBVEC(consdin):
210	halt
211SCBVEC(consdout):
212	halt
213#endif
214
215#if NDZ > 0
216/*
217 * DZ pseudo dma routine:
218 *	r0 - controller number
219 */
220	.align	1
221	.globl	_dzdma
222_dzdma:
223	mull2	$8*20,r0
224	movab	_dzpdma(r0),r3		# pdma structure base
225					# for this controller
226dzploop:
227	movl	r3,r0
228	movl	(r0)+,r1		# device register address
229	movzbl	1(r1),r2		# get line number
230	bitb	$0x80,r2		# TRDY on?
231	beql	dzprei			# no
232	bicb2	$0xf8,r2		# clear garbage bits
233	mull2	$20,r2
234	addl2	r2,r0			# point at line's pdma structure
235	movl	(r0)+,r2		# p_mem
236	cmpl	r2,(r0)+		# p_mem < p_end ?
237	bgequ	dzpcall			# no, go call dzxint
238	movb	(r2)+,6(r1)		# dztbuf = *p_mem++
239	movl	r2,-8(r0)
240	brb 	dzploop			# check for another line
241dzprei:
242	POPR
243	incl	_cnt+V_PDMA
244	rei
245
246dzpcall:
247	pushl	r3
248	pushl	(r0)+			# push tty address
249	calls	$1,*(r0)		# call interrupt rtn
250	movl	(sp)+,r3
251	brb 	dzploop			# check for another line
252#endif
253
254/*
255 * Stray UNIBUS interrupt catch routines
256 */
257	.data
258	.align	2
259#define	PJ	PUSHR;jsb _Xustray
260	.globl	_catcher
261_catcher:
262	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
263	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
264	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
265	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
266	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
267	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
268	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
269	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
270
271	.globl	_cold
272_cold:	.long	1
273	.data
274
275	.text
276SCBVEC(ustray):
277	blbc	_cold,1f
278	mfpr	$IPL,r11
279	subl3	$_catcher+8,(sp)+,r10
280	ashl	$-1,r10,r10
281	POPR
282	rei
2831:
284	subl3	$_catcher+8,(sp)+,r0
285	ashl	$-1,r0,-(sp)
286	mfpr	$IPL,-(sp)
287	PRINTF(2, "uba?: stray intr ipl %x vec %o\n")
288	POPR
289	rei
290
291/*
292 * Trap and fault vector routines
293 */
294#define	TRAP(a)	pushl $T_/**/a; jbr alltraps
295
296/*
297 * Ast delivery (profiling and/or reschedule)
298 */
299SCBVEC(astflt):
300	pushl $0; TRAP(ASTFLT)
301SCBVEC(privinflt):
302	pushl $0; TRAP(PRIVINFLT)
303SCBVEC(xfcflt):
304	pushl $0; TRAP(XFCFLT)
305SCBVEC(resopflt):
306	pushl $0; TRAP(RESOPFLT)
307SCBVEC(resadflt):
308	pushl $0; TRAP(RESADFLT)
309SCBVEC(bptflt):
310	pushl $0; TRAP(BPTFLT)
311SCBVEC(compatflt):
312	TRAP(COMPATFLT);
313SCBVEC(tracep):
314	pushl $0; TRAP(TRCTRAP)
315SCBVEC(arithtrap):
316	TRAP(ARITHTRAP)
317SCBVEC(protflt):
318	blbs	(sp)+,segflt
319	TRAP(PROTFLT)
320segflt:
321	TRAP(SEGFLT)
322SCBVEC(transflt):
323	bitl	$2,(sp)+
324	bnequ	tableflt
325	TRAP(PAGEFLT)
326tableflt:
327	TRAP(TABLEFLT)
328
329alltraps:
330	mfpr	$USP,-(sp); calls $0,_trap; mtpr (sp)+,$USP
331	incl	_cnt+V_TRAP
332	addl2	$8,sp			# pop type, code
333	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
334	rei
335
336SCBVEC(syscall):
337	pushl	$T_SYSCALL
338	mfpr	$USP,-(sp); calls $0,_syscall; mtpr (sp)+,$USP
339	incl	_cnt+V_SYSCALL
340	addl2	$8,sp			# pop type, code
341	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
342	rei
343
344/*
345 * System page table
346 */
347#define	vaddr(x)	((((x)-_Sysmap)/4)*NBPG+0x80000000)
348#define	SYSMAP(mname, vname, npte)			\
349_/**/mname:	.globl	_/**/mname;		\
350	.space	npte*4;				\
351	.globl	_/**/vname;			\
352	.set	_/**/vname,vaddr(_/**/mname)
353
354	.data
355	.align	2
356	SYSMAP(Sysmap	,Sysbase	,SYSPTSIZE	)
357	SYSMAP(UMBAbeg	,umbabeg	,0		)
358	SYSMAP(Nexmap	,nexus		,16*MAXNNEXUS	)
359	SYSMAP(UMEMmap	,umem		,512*MAXNUBA	)
360	SYSMAP(UMBAend	,umbaend	,0		)
361	SYSMAP(Usrptmap	,usrpt		,USRPTSIZE	)
362	SYSMAP(Forkmap	,forkutl	,UPAGES		)
363	SYSMAP(Xswapmap	,xswaputl	,UPAGES		)
364	SYSMAP(Xswap2map,xswap2utl	,UPAGES		)
365	SYSMAP(Swapmap	,swaputl	,UPAGES		)
366	SYSMAP(Pushmap	,pushutl	,UPAGES		)
367	SYSMAP(Vfmap	,vfutl		,UPAGES		)
368	SYSMAP(CMAP1	,CADDR1		,1		)
369	SYSMAP(CMAP2	,CADDR2		,1		)
370	SYSMAP(mcrmap	,mcr		,1		)
371	SYSMAP(mmap	,vmmap		,1		)
372	SYSMAP(msgbufmap,msgbuf		,MSGBUFPTECNT	)
373	SYSMAP(camap	,cabase		,16*CLSIZE	)
374	SYSMAP(ecamap	,calimit	,0		)
375	SYSMAP(Mbmap	,mbutl		,NMBCLUSTERS*CLSIZE)
376
377eSysmap:
378	.globl	_Syssize
379	.set	_Syssize,(eSysmap-_Sysmap)/4
380	.text
381
382/*
383 * Initialization
384 *
385 * ipl 0x1f; mapen 0; scbb, pcbb, sbr, slr, isp, ksp not set
386 */
387	.data
388	.globl	_cpu
389_cpu:	.long	0
390	.text
391	.globl	start
392start:
393	.word	0
394/* set system control block base and system page table params */
395	mtpr	$_scb-0x80000000,$SCBB
396	mtpr	$_Sysmap-0x80000000,$SBR
397	mtpr	$_Syssize,$SLR
398/* double map the kernel into the virtual user addresses of phys mem */
399	mtpr	$_Sysmap,$P0BR
400	mtpr	$_Syssize,$P0LR
401/* set ISP and get cpu type */
402	movl	$_intstack+NISP*NBPG,sp
403	mfpr	$SID,r0
404	movab	_cpu,r1
405	extzv	$24,$8,r0,(r1)
406/* init RPB */
407	movab	_rpb,r0
408	movl	r0,(r0)+			# rp_selfref
409	movab	_doadump,r1
410	movl	r1,(r0)+			# rp_dumprout
411	movl	$0x1f,r2
412	clrl	r3
4131:	addl2	(r1)+,r3; sobgtr r2,1b
414	movl	r3,(r0)+			# rp_chksum
415/* count up memory */
416	clrl	r7
4171:	pushl	$4; pushl r7; calls $2,_badaddr; tstl r0; bneq 9f
418	acbl	$8192*1024-1,$64*1024,r7,1b
4199:
420/* clear memory from kernel bss and pages for proc 0 u. and page table */
421	movab	_edata,r6
422	movab	_end,r5
423	bbcc	$31,r5,0f; 0:
424	addl2	$(UPAGES*NBPG)+NBPG+NBPG,r5
4251:	clrq	(r6); acbl r5,$8,r6,1b
426/* trap() and syscall() save r0-r11 in the entry mask (per ../h/reg.h) */
427	bisw2	$0x0fff,_trap
428	bisw2	$0x0fff,_syscall
429	calls	$0,_fixctlrmask
430/* initialize system page table: scb and int stack writeable */
431	clrl	r2
432	movab	eintstack,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
4331:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
434/* make rpb read-only as red zone for interrupt stack */
435	bicl2	$PG_PROT,_rpbmap
436	bisl2	$PG_KR,_rpbmap
437/* make kernel text space read-only */
438	movab	_etext+NBPG-1,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
4391:	bisl3	$PG_V|PG_KR,r2,_Sysmap[r2]; aoblss r1,r2,1b
440/* make kernel data, bss, read-write */
441	movab	_end+NBPG-1,r1; bbcc $31,r1,0f; 0:; ashl $-PGSHIFT,r1,r1
4421:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
443/* now go to mapped mode */
444	mtpr	$1,$TBIA; mtpr $1,$MAPEN; jmp *$0f; 0:
445/* init mem sizes */
446	ashl	$-PGSHIFT,r7,_maxmem
447	movl	_maxmem,_physmem
448	movl	_maxmem,_freemem
449/* setup context for proc[0] == Scheduler */
450	movab	_end+NBPG-1,r6
451	bicl2	$NBPG-1,r6		# make page boundary
452/* setup page table for proc[0] */
453	bbcc	$31,r6,0f; 0:
454	ashl	$-PGSHIFT,r6,r3			# r3 = btoc(r6)
455	bisl3	$PG_V|PG_KW,r3,_Usrptmap	# init first upt entry
456	incl	r3
457	movab	_usrpt,r0
458	mtpr	r0,$TBIS
459/* init p0br, p0lr */
460	mtpr	r0,$P0BR
461	mtpr	$0,$P0LR
462/* init p1br, p1lr */
463	movab	NBPG(r0),r0
464	movl	$0x200000-UPAGES,r1
465	mtpr	r1,$P1LR
466	mnegl	r1,r1
467	moval	-4*UPAGES(r0)[r1],r2
468	mtpr	r2,$P1BR
469/* setup mapping for UPAGES of _u */
470	movl	$UPAGES,r2; movab _u+NBPG*UPAGES,r1; addl2 $UPAGES,r3; jbr 2f
4711:	decl	r3
472	moval	-NBPG(r1),r1;
473	bisl3	$PG_V|PG_URKW,r3,-(r0)
474	mtpr	r1,$TBIS
4752:	sobgeq	r2,1b
476/* initialize (slightly) the pcb */
477	movab	UPAGES*NBPG(r1),PCB_KSP(r1)
478	mnegl	$1,PCB_ESP(r1)
479	mnegl	$1,PCB_SSP(r1)
480	movl	r1,PCB_USP(r1)
481	mfpr	$P0BR,PCB_P0BR(r1)
482	mfpr	$P0LR,PCB_P0LR(r1)
483	movb	$4,PCB_P0LR+3(r1)		# disable ast
484	mfpr	$P1BR,PCB_P1BR(r1)
485	mfpr	$P1LR,PCB_P1LR(r1)
486	movl	$CLSIZE,PCB_SZPT(r1)		# init u.u_pcb.pcb_szpt
487	movl	r11,PCB_R11(r1)
488	movab	1f,PCB_PC(r1)			# initial pc
489	clrl	PCB_PSL(r1)			# mode(k,k), ipl=0
490	ashl	$PGSHIFT,r3,r3
491	mtpr	r3,$PCBB			# first pcbb
492/* set regs, p0br, p0lr, p1br, p1lr, astlvl, ksp and change to kernel mode */
493	ldpctx
494	rei
495/* put signal trampoline code in u. area */
4961:	movab	_u,r0
497	movc3	$12,sigcode,PCB_SIGC(r0)
498/* save reboot flags in global _boothowto */
499	movl	r11,_boothowto
500/* calculate firstaddr, and call main() */
501	movab	_end+NBPG-1,r0; bbcc $31,r0,0f; 0:; ashl $-PGSHIFT,r0,-(sp)
502	addl2	$UPAGES+1,(sp); calls $1,_main
503/* proc[1] == /etc/init now running here; run icode */
504	pushl	$PSL_CURMOD|PSL_PRVMOD; pushl $0; rei
505
506/* signal trampoline code: it is known that this code takes exactly 12 bytes */
507/* in ../h/pcb.h and in the movc3 above */
508sigcode:
509	calls	$3,1(pc)
510	rei
511	.word	0x7f				# registers 0-6 (6==sp/compat)
512	callg	(ap),*12(ap)
513	ret
514
515/*
516 * Primitives
517 */
518
519/*
520 * badaddr(addr, len)
521 *	see if access addr with a len type instruction causes a machine check
522 *	len is length of access (1=byte, 2=short, 4=long)
523 */
524	.globl	_badaddr
525_badaddr:
526	.word	0
527	movl	$1,r0
528	mfpr	$IPL,r1
529	mtpr	$HIGH,$IPL
530	movl	_scb+MCKVEC,r2
531	movl	4(ap),r3
532	movl	8(ap),r4
533	movab	9f+INTSTK,_scb+MCKVEC
534	bbc	$0,r4,1f; tstb	(r3)
5351:	bbc	$1,r4,1f; tstw	(r3)
5361:	bbc	$2,r4,1f; tstl	(r3)
5371:	clrl	r0			# made it w/o machine checks
5382:	movl	r2,_scb+MCKVEC
539	mtpr	r1,$IPL
540	ret
541	.align	2
5429:
543	casel	_cpu,$1,$VAX_MAX
5440:
545	.word	8f-0b		# 1 is 780
546	.word	5f-0b		# 2 is 750
547	.word	5f-0b		# 3 is 730
5485:
549#if defined(VAX750) || defined(VAX730)
550	mtpr	$0xf,$MCESR
551#endif
552	brb	1f
5538:
554#if VAX780
555	mtpr	$0,$SBIFS
556#endif
5571:
558	addl2	(sp)+,sp		# discard mchchk trash
559	movab	2b,(sp)
560	rei
561
562_Copyin:	.globl	_Copyin		# <<<massaged for jsb by asm.sed>>>
563	movl	12(sp),r0		# copy length
564	blss	ersb
565	movl	4(sp),r1		# copy user address
566	cmpl	$NBPG,r0		# probing one page or less ?
567	bgeq	cishort			# yes
568ciloop:
569	prober	$3,$NBPG,(r1)		# bytes accessible ?
570	beql	ersb			# no
571	addl2	$NBPG,r1		# incr user address ptr
572	acbl	$NBPG+1,$-NBPG,r0,ciloop	# reduce count and loop
573cishort:
574	prober	$3,r0,(r1)		# bytes accessible ?
575	beql	ersb			# no
576	movl	4(sp),r1
577	movl	8(sp),r3
578	jbr	2f
5791:
580	subl2	r0,12(sp)
581	movc3	r0,(r1),(r3)
5822:
583	movzwl	$65535,r0
584	cmpl	12(sp),r0
585	jgtr	1b
586	movc3	12(sp),(r1),(r3)
587	clrl	r0			#redundant
588	rsb
589
590ersb:
591	mnegl	$1,r0
592	rsb
593
594_Copyout: 	.globl	_Copyout	# <<<massaged for jsb by asm.sed >>>
595	movl	12(sp),r0		# get count
596	blss	ersb
597	movl	8(sp),r1		# get user address
598	cmpl	$NBPG,r0		# can do in one probew?
599	bgeq	coshort			# yes
600coloop:
601	probew	$3,$NBPG,(r1)		# bytes accessible?
602	beql	ersb			# no
603	addl2	$NBPG,r1		# increment user address
604	acbl	$NBPG+1,$-NBPG,r0,coloop	# reduce count and loop
605coshort:
606	probew	$3,r0,(r1)		# bytes accessible?
607	beql	ersb			# no
608	movl	4(sp),r1
609	movl	8(sp),r3
610	jbr	2f
6111:
612	subl2	r0,12(sp)
613	movc3	r0,(r1),(r3)
6142:
615	movzwl	$65535,r0
616	cmpl	12(sp),r0
617	jgtr	1b
618	movc3	12(sp),(r1),(r3)
619	clrl	r0				#redundant
620	rsb
621
622/*
623 * non-local goto's
624 */
625	.globl	_Setjmp
626_Setjmp:
627	movq	r6,(r0)+
628	movq	r8,(r0)+
629	movq	r10,(r0)+
630	movq	r12,(r0)+
631	addl3	$4,sp,(r0)+
632	movl	(sp),(r0)
633	clrl	r0
634	rsb
635
636	.globl	_Longjmp
637_Longjmp:
638	movq	(r0)+,r6
639	movq	(r0)+,r8
640	movq	(r0)+,r10
641	movq	(r0)+,r12
642	movl	(r0)+,r1
643	cmpl	r1,sp				# must be a pop
644	bgequ	lj2
645	pushab	lj1
646	calls	$1,_panic
647lj2:
648	movl	r1,sp
649	jmp	*(r0)				# ``rsb''
650
651lj1:	.asciz	"longjmp"
652
653	.globl	_whichqs
654	.globl	_qs
655	.globl	_cnt
656
657	.globl	_noproc
658	.comm	_noproc,4
659	.globl	_runrun
660	.comm	_runrun,4
661
662/*
663 * The following primitives use the fancy VAX instructions
664 * much like VMS does.  _whichqs tells which of the 32 queues _qs
665 * have processes in them.  Setrq puts processes into queues, Remrq
666 * removes them from queues.  The running process is on no queue,
667 * other processes are on a queue related to p->p_pri, divided by 4
668 * actually to shrink the 0-127 range of priorities into the 32 available
669 * queues.
670 */
671
672/*
673 * Setrq(p), using fancy VAX instructions.
674 *
675 * Call should be made at spl6(), and p->p_stat should be SRUN
676 */
677	.globl	_Setrq		# <<<massaged to jsb by "asm.sed">>>
678_Setrq:
679	tstl	P_RLINK(r0)		## firewall: p->p_rlink must be 0
680	beql	set1			##
681	pushab	set3			##
682	calls	$1,_panic		##
683set1:
684	movzbl	P_PRI(r0),r1		# put on queue which is p->p_pri / 4
685	ashl	$-2,r1,r1
686	movaq	_qs[r1],r2
687	insque	(r0),*4(r2)		# at end of queue
688	bbss	r1,_whichqs,set2	# mark queue non-empty
689set2:
690	rsb
691
692set3:	.asciz	"setrq"
693
694/*
695 * Remrq(p), using fancy VAX instructions
696 *
697 * Call should be made at spl6().
698 */
699	.globl	_Remrq		# <<<massaged to jsb by "asm.sed">>>
700_Remrq:
701	movzbl	P_PRI(r0),r1
702	ashl	$-2,r1,r1
703	bbsc	r1,_whichqs,rem1
704	pushab	rem3			# it wasn't recorded to be on its q
705	calls	$1,_panic
706rem1:
707	remque	(r0),r2
708	beql	rem2
709	bbss	r1,_whichqs,rem2
710rem2:
711	clrl	P_RLINK(r0)		## for firewall checking
712	rsb
713
714rem3:	.asciz	"remrq"
715
716/*
717 * Masterpaddr is the p->p_addr of the running process on the master
718 * processor.  When a multiprocessor system, the slave processors will have
719 * an array of slavepaddr's.
720 */
721	.globl	_masterpaddr
722	.data
723_masterpaddr:
724	.long	0
725
726	.text
727sw0:	.asciz	"swtch"
728/*
729 * Swtch(), using fancy VAX instructions
730 */
731	.globl	_Swtch
732_Swtch:				# <<<massaged to jsb by "asm.sed">>>
733	movl	$1,_noproc
734	clrl	_runrun
735sw1:	ffs	$0,$32,_whichqs,r0	# look for non-empty queue
736	bneq	sw1a
737	mtpr	$0,$IPL			# must allow interrupts here
738	jbr	sw1			# this is an idle loop!
739sw1a:	mtpr	$0x18,$IPL		# lock out all so _whichqs==_qs
740	bbcc	r0,_whichqs,sw1		# proc moved via lbolt interrupt
741	movaq	_qs[r0],r1
742	remque	*(r1),r2		# r2 = p = highest pri process
743	bvc	sw2			# make sure something was there
744sw1b:	pushab	sw0
745	calls	$1,_panic
746sw2:	beql	sw3
747	insv	$1,r0,$1,_whichqs	# still more procs in this queue
748sw3:
749	clrl	_noproc
750	tstl	P_WCHAN(r2)		## firewalls
751	bneq	sw1b			##
752	movzbl	P_STAT(r2),r3		##
753	cmpl	$SRUN,r3		##
754	bneq	sw1b			##
755	clrl	P_RLINK(r2)		##
756	movl	*P_ADDR(r2),r0
757	movl	r0,_masterpaddr
758	ashl	$PGSHIFT,r0,r0		# r0 = pcbb(p)
759/*	mfpr	$PCBB,r1		# resume of current proc is easy
760 *	cmpl	r0,r1
761 */	beql	res0
762	incl	_cnt+V_SWTCH
763/* fall into... */
764
765/*
766 * Resume(pf)
767 */
768	.globl	_Resume		# <<<massaged to jsb by "asm.sed">>>
769_Resume:
770	mtpr	$0x18,$IPL			# no interrupts, please
771	movl	_CMAP2,_u+PCB_CMAP2	# yech
772	svpctx
773	mtpr	r0,$PCBB
774	ldpctx
775	movl	_u+PCB_CMAP2,_CMAP2	# yech
776	mtpr	$_CADDR2,$TBIS
777res0:
778	tstl	_u+PCB_SSWAP
779	beql	res1
780	movl	_u+PCB_SSWAP,r0
781	clrl	_u+PCB_SSWAP
782	movab	_Longjmp,(sp)
783	movl	$PSL_PRVMOD,4(sp)		# ``cheating'' (jfr)
784res1:
785	rei
786
787/*
788 * {fu,su},{byte,word}, all massaged by asm.sed to jsb's
789 */
790	.globl	_Fuword
791_Fuword:
792	prober	$3,$4,(r0)
793	beql	fserr
794	movl	(r0),r0
795	rsb
796fserr:
797	mnegl	$1,r0
798	rsb
799
800	.globl	_Fubyte
801_Fubyte:
802	prober	$3,$1,(r0)
803	beql	fserr
804	movzbl	(r0),r0
805	rsb
806
807	.globl	_Suword
808_Suword:
809	probew	$3,$4,(r0)
810	beql	fserr
811	movl	r1,(r0)
812	clrl	r0
813	rsb
814
815	.globl	_Subyte
816_Subyte:
817	probew	$3,$1,(r0)
818	beql	fserr
819	movb	r1,(r0)
820	clrl	r0
821	rsb
822
823/*
824 * Copy 1 relocation unit (NBPG bytes)
825 * from user virtual address to physical address
826 */
827_copyseg: 	.globl	_copyseg
828	.word	0x0
829	bisl3	$PG_V|PG_KW,8(ap),_CMAP2
830	mtpr	$_CADDR2,$TBIS	# invalidate entry for copy
831	movc3	$NBPG,*4(ap),_CADDR2
832	ret
833
834/*
835 * zero out physical memory
836 * specified in relocation units (NBPG bytes)
837 */
838_clearseg: 	.globl	_clearseg
839	.word	0x0
840	bisl3	$PG_V|PG_KW,4(ap),_CMAP1
841	mtpr	$_CADDR1,$TBIS
842	movc5	$0,(sp),$0,$NBPG,_CADDR1
843	ret
844
845/*
846 * Check address.
847 * Given virtual address, byte count, and rw flag
848 * returns 0 on no access.
849 */
850_useracc:	.globl	_useracc
851	.word	0x0
852	movl	4(ap),r0		# get va
853	movl	8(ap),r1		# count
854	tstl	12(ap)			# test for read access ?
855	bneq	userar			# yes
856	cmpl	$NBPG,r1			# can we do it in one probe ?
857	bgeq	uaw2			# yes
858uaw1:
859	probew	$3,$NBPG,(r0)
860	beql	uaerr			# no access
861	addl2	$NBPG,r0
862	acbl	$NBPG+1,$-NBPG,r1,uaw1
863uaw2:
864	probew	$3,r1,(r0)
865	beql	uaerr
866	movl	$1,r0
867	ret
868
869userar:
870	cmpl	$NBPG,r1
871	bgeq	uar2
872uar1:
873	prober	$3,$NBPG,(r0)
874	beql	uaerr
875	addl2	$NBPG,r0
876	acbl	$NBPG+1,$-NBPG,r1,uar1
877uar2:
878	prober	$3,r1,(r0)
879	beql	uaerr
880	movl	$1,r0
881	ret
882uaerr:
883	clrl	r0
884	ret
885
886/*
887 * kernacc - check for kernel access privileges
888 *
889 * We can't use the probe instruction directly because
890 * it ors together current and previous mode.
891 */
892	.globl	_kernacc
893_kernacc:
894	.word	0x0
895	movl	4(ap),r0	# virtual address
896	bbcc	$31,r0,kacc1
897	bbs	$30,r0,kacerr
898	mfpr	$SBR,r2		# address and length of page table (system)
899	bbss	$31,r2,0f; 0:
900	mfpr	$SLR,r3
901	brb	kacc2
902kacc1:
903	bbsc	$30,r0,kacc3
904	mfpr	$P0BR,r2	# user P0
905	mfpr	$P0LR,r3
906	brb	kacc2
907kacc3:
908	mfpr	$P1BR,r2	# user P1 (stack)
909	mfpr	$P1LR,r3
910kacc2:
911	addl3	8(ap),r0,r1	# ending virtual address
912	addl2	$NBPG-1,r1
913	ashl	$-PGSHIFT,r0,r0
914	ashl	$-PGSHIFT,r1,r1
915	bbs	$31,4(ap),kacc6
916	bbc	$30,4(ap),kacc6
917	cmpl	r0,r3		# user stack
918	blss	kacerr		# address too low
919	brb	kacc4
920kacc6:
921	cmpl	r1,r3		# compare last page to P0LR or SLR
922	bgtr	kacerr		# address too high
923kacc4:
924	movl	(r2)[r0],r3
925	bbc	$31,4(ap),kacc4a
926	bbc	$31,r3,kacerr	# valid bit is off
927kacc4a:
928	cmpzv	$27,$4,r3,$1	# check protection code
929	bleq	kacerr		# no access allowed
930	tstb	12(ap)
931	bneq	kacc5		# only check read access
932	cmpzv	$27,$2,r3,$3	# check low 2 bits of prot code
933	beql	kacerr		# no write access
934kacc5:
935	aoblss	r1,r0,kacc4	# next page
936	movl	$1,r0		# no errors
937	ret
938kacerr:
939	clrl	r0		# error
940	ret
941