xref: /original-bsd/sys/vax/vax/locore.s (revision cd18b70b)
1/*
2 * Copyright (c) 1980, 1986 Regents of the University of California.
3 * All rights reserved.  The Berkeley software License Agreement
4 * specifies the terms and conditions for redistribution.
5 *
6 *	@(#)locore.s	7.7 (Berkeley) 08/07/87
7 */
8
9#include "psl.h"
10#include "pte.h"
11
12#include "errno.h"
13#include "cmap.h"
14
15#include "mtpr.h"
16#include "trap.h"
17#include "cpu.h"
18#include "nexus.h"
19#include "cons.h"
20#include "clock.h"
21#include "ioa.h"
22#include "ka630.h"
23#include "../vaxuba/ubareg.h"
24
25#include "dz.h"
26#include "uu.h"
27#include "ps.h"
28#include "mba.h"
29#include "uba.h"
30
31	.set	HIGH,0x1f	# mask for total disable
32	.set	MCKVEC,4	# offset into scb of machine check vector
33	.set	NBPG,512
34	.set	PGSHIFT,9
35	.set	SYSTEM,0x80000000	# virtual address of system start
36
37	.set	NISP,3		# number of interrupt stack pages
38
39/*
40 * User structure is UPAGES at top of user space.
41 */
42	.globl	_u
43	.set	_u,0x80000000 - UPAGES*NBPG
44
45	.globl	_intstack
46_intstack:
47	.space	NISP*NBPG
48eintstack:
49
50/*
51 * Do a dump.
52 * Called by auto-restart.
53 * May be called manually.
54 */
55	.align	2
56	.globl	_doadump
57_doadump:
58	nop; nop				# .word 0x0101
59#define	_rpbmap	_Sysmap				# rpb, scb, UNI*vec, istack*4
60	bicl2	$PG_PROT,_rpbmap
61	bisl2	$PG_KW,_rpbmap
62	mtpr	$0,$TBIA
63	tstl	_rpb+RP_FLAG			# dump only once!
64	bneq	1f
65	incl	_rpb+RP_FLAG
66	movl	sp,erpb
67	movab	erpb,sp
68	mfpr	$PCBB,-(sp)
69	mfpr	$MAPEN,-(sp)
70	mfpr	$IPL,-(sp)
71	mtpr	$0,$MAPEN
72	mtpr	$HIGH,$IPL
73	pushr	$0x3fff
74	calls	$0,_dumpsys
751:
76	pushl	$TXDB_BOOT
77	calls	$1,_tocons
78	halt
79
80/*
81 * Interrupt vector routines
82 */
83	.globl	_waittime
84
85#define	SCBVEC(name)	.align 2; .globl _X/**/name; _X/**/name
86#define	PANIC(msg)	clrl _waittime; pushab 1f; \
87			calls $1,_panic; 1: .asciz msg
88#define	PRINTF(n,msg)	pushab 1f; calls $n+1,_printf; MSG(msg)
89#define	MSG(msg)	.data; 1: .asciz msg; .text
90#define	PUSHR		pushr $0x3f
91#define	POPR		popr $0x3f
92
93	.data
94nofault: .long	0	# where to go on predicted machcheck
95	.text
96SCBVEC(machcheck):
97	tstl	nofault
98	bneq	1f
99	PUSHR; pushab 6*4(sp); calls $1,_machinecheck; POPR;
100	addl2 (sp)+,sp; rei
101	.align	2
1021:
103	casel	_cpu,$1,$VAX_MAX
1040:
105	.word	8f-0b		# 1 is 780
106	.word	5f-0b		# 2 is 750
107	.word	5f-0b		# 3 is 730
108	.word	7f-0b		# 4 is 8600
109	.word	1f-0b		# ???
110	.word	1f-0b		# ???
111	.word	1f-0b		# ???
112	.word	1f-0b		# 8 is 630
1135:
114#if defined(VAX750) || defined(VAX730)
115	mtpr	$0xf,$MCESR
116#endif
117	brb	1f
1187:
119#if VAX8600
120	mtpr	$0,$EHSR
121#endif
122	brb	1f
1238:
124#if VAX780
125	mtpr	$0,$SBIFS
126#endif
1271:
128	addl2	(sp)+,sp		# discard mchchk trash
129	movl	nofault,(sp)
130	rei
131SCBVEC(kspnotval):
132	PUSHR; PANIC("KSP not valid");
133SCBVEC(powfail):
134	halt
135SCBVEC(chme): SCBVEC(chms): SCBVEC(chmu):
136	PUSHR; PANIC("CHM? in kernel");
137SCBVEC(stray):
138	PUSHR; PRINTF(0, "stray scb interrupt\n"); POPR;
139	rei
140SCBVEC(nexzvec):
141	PUSHR; mfpr $IPL,-(sp); PRINTF(1, "nexus stray intr ipl%x\n"); POPR; rei
142SCBVEC(cmrd):
143	PUSHR; calls $0,_memerr; POPR; rei
144SCBVEC(wtime):
145	PUSHR; pushl 6*4(sp); PRINTF(1,"write timeout %x\n"); POPR;
146	PANIC("wtimo");
147
148#if NMBA > 0
149SCBVEC(mba3int):
150	PUSHR; incl _intrcnt+I_MBA3; pushl $3; brb 1f
151SCBVEC(mba2int):
152	PUSHR; incl _intrcnt+I_MBA2; pushl $2; brb 1f
153SCBVEC(mba1int):
154	PUSHR; incl _intrcnt+I_MBA1; pushl $1; brb 1f
155SCBVEC(mba0int):
156	PUSHR; incl _intrcnt+I_MBA0; pushl $0
1571:	calls $1,_mbintr
158	POPR
159	incl	_cnt+V_INTR
160	rei
161#endif
162
163#ifdef DW780
164/*
165 * Registers for the uba handling code
166 */
167#define	rUBANUM	r0
168#define	rUBAHD	r1
169#define	rUVEC	r3
170#define	rUBA	r4
171/* r2,r5 are scratch */
172
173#define	I_UBA	I_UBA0		/* base of UBA interrupt counters */
174
175#if NUBA > 4
176SCBVEC(ua7int):
177	PUSHR; movl $7,rUBANUM; moval _uba_hd+(7*UH_SIZE),rUBAHD; brb 1f
178SCBVEC(ua6int):
179	PUSHR; movl $6,rUBANUM; moval _uba_hd+(6*UH_SIZE),rUBAHD; brb 1f
180SCBVEC(ua5int):
181	PUSHR; movl $5,rUBANUM; moval _uba_hd+(5*UH_SIZE),rUBAHD; brb 1f
182SCBVEC(ua4int):
183	PUSHR; movl $4,rUBANUM; moval _uba_hd+(4*UH_SIZE),rUBAHD; brb 1f
184#endif
185SCBVEC(ua3int):
186	PUSHR; movl $3,rUBANUM; moval _uba_hd+(3*UH_SIZE),rUBAHD; brb 1f
187SCBVEC(ua2int):
188	PUSHR; movl $2,rUBANUM; moval _uba_hd+(2*UH_SIZE),rUBAHD; brb 1f
189SCBVEC(ua1int):
190	PUSHR; movl $1,rUBANUM; moval _uba_hd+(1*UH_SIZE),rUBAHD; brb 1f
191SCBVEC(ua0int):
192	PUSHR; movl $0,rUBANUM; moval _uba_hd+(0*UH_SIZE),rUBAHD;
1931:
194	mfpr	$IPL,r2				/* r2 = mfpr(IPL); */
195	movl	UH_UBA(rUBAHD),rUBA		/* uba = uhp->uh_uba; */
196	movl	UBA_BRRVR-0x14*4(rUBA)[r2],rUVEC
197					/* uvec = uba->uba_brrvr[r2-0x14] */
198ubanorm:
199	bleq	ubaerror
200	addl2	UH_VEC(rUBAHD),rUVEC		/* uvec += uh->uh_vec */
201	bicl3	$3,(rUVEC),r1
202	jmp	2(r1)				/* 2 skips ``pushr $0x3f'' */
203ubaerror:
204	PUSHR; calls $0,_ubaerror; POPR		/* ubaerror r/w's r0-r5 */
205	tstl rUVEC; jneq ubanorm		/* rUVEC contains result */
206	incl _intrcnt+I_UBA[rUBANUM]
207	incl	_cnt+V_INTR
208	POPR
209	rei
210#endif
211SCBVEC(cnrint):
212	PUSHR; calls $0,_cnrint; POPR
213	incl _cnt+V_INTR
214	incl _intrcnt+I_CNR
215	rei
216SCBVEC(cnxint):
217	PUSHR; calls $0,_cnxint; POPR
218	incl _cnt+V_INTR
219	incl _intrcnt+I_CNX
220	rei
221SCBVEC(hardclock):
222	PUSHR
223	mtpr $ICCS_RUN|ICCS_IE|ICCS_INT|ICCS_ERR,$ICCS
224#if NPS > 0
225	pushl	4+6*4(sp); pushl 4+6*4(sp);
226	calls	$2,_psextsync
227#endif
228	pushl 4+6*4(sp); pushl 4+6*4(sp);
229	calls $2,_hardclock			# hardclock(pc,psl)
230	POPR;
231	incl	_cnt+V_INTR
232	incl	_intrcnt+I_CLOCK
233	rei
234SCBVEC(softclock):
235	PUSHR
236	pushl	4+6*4(sp); pushl 4+6*4(sp);
237	calls	$2,_softclock			# softclock(pc,psl)
238	POPR;
239	incl	_cnt+V_SOFT
240	rei
241
242#include "../net/netisr.h"
243	.globl	_netisr
244SCBVEC(netintr):
245	PUSHR
246#include "imp.h"
247#if NIMP > 0
248	bbcc	$NETISR_IMP,_netisr,1f; calls $0,_impintr; 1:
249#endif
250#ifdef INET
251	bbcc	$NETISR_IP,_netisr,1f; calls $0,_ipintr; 1:
252#endif
253#ifdef NS
254	bbcc	$NETISR_NS,_netisr,1f; calls $0,_nsintr; 1:
255#endif
256	bbcc	$NETISR_RAW,_netisr,1f; calls $0,_rawintr; 1:
257	POPR
258	incl	_cnt+V_SOFT
259	rei
260
261#if defined(VAX750) || defined(VAX730) || defined(VAX8600)
262SCBVEC(consdin):
263	PUSHR;
264	incl _intrcnt+I_TUR
265	casel	_cpu,$VAX_750,$VAX_8600
2660:
267	.word	5f-0b		# 2 is VAX_750
268	.word	3f-0b		# 3 is VAX_730
269	.word	6f-0b		# 4 is VAX_8600
270	halt
2715:
272#if defined(VAX750) && !defined(MRSP)
273	jsb	tudma
274#endif
2753:
276#if defined(VAX750) || defined(VAX730)
277	calls $0,_turintr
278	brb 2f
279#else
280	halt
281#endif
2826:
283#if VAX8600
284	calls $0, _crlintr
285#else
286	halt
287#endif
2882:
289	POPR;
290	incl _cnt+V_INTR;
291	rei
292#else
293SCBVEC(consdin):
294	halt
295#endif
296
297#if defined(VAX750) || defined(VAX730)
298SCBVEC(consdout):
299	PUSHR; calls $0,_tuxintr; POPR
300	incl _cnt+V_INTR
301	incl _intrcnt+I_TUX
302	rei
303#else
304SCBVEC(consdout):
305	halt
306#endif
307
308#if NDZ > 0
309/*
310 * DZ pseudo dma routine:
311 *	r0 - controller number
312 */
313	.align	1
314	.globl	dzdma
315dzdma:
316	mull2	$8*20,r0
317	movab	_dzpdma(r0),r3		# pdma structure base
318					# for this controller
319dzploop:
320	movl	r3,r0
321	movl	(r0)+,r1		# device register address
322	movzbl	1(r1),r2		# get line number
323	bitb	$0x80,r2		# TRDY on?
324	beql	dzprei			# no
325	bicb2	$0xf8,r2		# clear garbage bits
326	mull2	$20,r2
327	addl2	r2,r0			# point at line's pdma structure
328	movl	(r0)+,r2		# p_mem
329	cmpl	r2,(r0)+		# p_mem < p_end ?
330	bgequ	dzpcall			# no, go call dzxint
331	movb	(r2)+,6(r1)		# dztbuf = *p_mem++
332	movl	r2,-8(r0)
333	brb 	dzploop			# check for another line
334dzprei:
335	POPR
336	incl	_cnt+V_PDMA
337	rei
338
339dzpcall:
340	pushl	r3
341	pushl	(r0)+			# push tty address
342	calls	$1,*(r0)		# call interrupt rtn
343	movl	(sp)+,r3
344	brb 	dzploop			# check for another line
345#endif
346
347#if NUU > 0 && defined(UUDMA)
348/*
349 * Pseudo DMA routine for tu58 (on DL11)
350 *	r0 - controller number
351 */
352	.align	1
353	.globl	uudma
354uudma:
355	movl	_uudinfo[r0],r2
356	movl	16(r2),r2		# r2 = uuaddr
357	mull3	$48,r0,r3
358	movab	_uu_softc(r3),r5	# r5 = uuc
359
360	cvtwl	2(r2),r1		# c = uuaddr->rdb
361	bbc	$15,r1,1f		# if (c & UUDB_ERROR)
362	movl	$13,16(r5)		#	uuc->tu_state = TUC_RCVERR;
363	rsb				#	let uurintr handle it
3641:
365	tstl	4(r5)			# if (uuc->tu_rcnt) {
366	beql	1f
367	movb	r1,*0(r5)		#	*uuc->tu_rbptr++ = r1
368	incl	(r5)
369	decl	4(r5)			#	if (--uuc->tu_rcnt)
370	beql	2f			#		done
371	tstl	(sp)+
372	POPR				# 	registers saved in ubglue.s
373	rei				# }
3742:
375	cmpl	16(r5),$8		# if (uuc->tu_state != TUS_GETH)
376	beql	2f			# 	let uurintr handle it
3771:
378	rsb
3792:
380	mull2	$14,r0			# sizeof(uudata[ctlr]) = 14
381	movab	_uudata(r0),r4		# data = &uudata[ctlr];
382	cmpb	$1,(r4)			# if (data->pk_flag != TUF_DATA)
383	bneq	1b
384#ifdef notdef
385	/* this is for command packets */
386	beql	1f			# 	r0 = uuc->tu_rbptr
387	movl	(r5),r0
388	brb	2f
3891:					# else
390#endif
391	movl	24(r5),r0		# 	r0 = uuc->tu_addr
3922:
393	movzbl	1(r4),r3		# counter to r3 (data->pk_count)
394	movzwl	(r4),r1			# first word of checksum (=header)
395	mfpr	$IPL,-(sp)		# s = spl5();
396	mtpr	$0x15,$IPL		# to keep disk interrupts out
397	clrw	(r2)			# disable receiver interrupts
3983:	bbc	$7,(r2),3b		# while ((uuaddr->rcs & UUCS_READY)==0);
399	cvtwb	2(r2),(r0)+		# *buffer = uuaddr->rdb & 0xff
400	sobgtr	r3,1f			# continue with next byte ...
401	addw2	2(r2),r1		# unless this was the last (odd count)
402	brb	2f
403
4041:	bbc	$7,(r2),1b		# while ((uuaddr->rcs & UUCS_READY)==0);
405	cvtwb	2(r2),(r0)+		# *buffer = uuaddr->rdb & 0xff
406	addw2	-2(r0),r1		# add to checksum..
4072:
408	adwc	$0,r1			# get the carry
409	sobgtr	r3,3b			# loop while r3 > 0
410/*
411 * We're ready to get the checksum
412 */
4131:	bbc	$7,(r2),1b		# while ((uuaddr->rcs & UUCS_READY)==0);
414	cvtwb	2(r2),12(r4)		# get first (lower) byte
4151:	bbc	$7,(r2),1b
416	cvtwb	2(r2),13(r4)		# ..and second
417	cmpw	12(r4),r1		# is checksum ok?
418	beql	1f
419	movl	$14,16(r5)		# uuc->tu_state = TUS_CHKERR
420	brb	2f			# exit
4211:
422	movl	$11,16(r5)		# uuc->tu_state = TUS_GET (ok)
4232:
424	movw	$0x40,(r2)		# enable receiver interrupts
425	mtpr	(sp)+,$IPL		# splx(s);
426	rsb				# continue processing in uurintr
427#endif
428
429#if defined(VAX750) && !defined(MRSP)
430/*
431 * Pseudo DMA routine for VAX-11/750 console tu58
432 *   	    (without MRSP)
433 */
434	.align	1
435	.globl	tudma
436tudma:
437	movab	_tu,r5			# r5 = tu
438	tstl	4(r5)			# if (tu.tu_rcnt) {
439	beql	3f
440	mfpr	$CSRD,r1		# get data from tu58
441	movb	r1,*0(r5)		#	*tu.tu_rbptr++ = r1
442	incl	(r5)
443	decl	4(r5)			#	if (--tu.tu_rcnt)
444	beql	1f			#		done
445	tstl	(sp)+
446	POPR				# 	registers saved in ubglue.s
447	rei				# 	data handled, done
4481:					# }
449	cmpl	16(r5),$8		# if (tu.tu_state != TUS_GETH)
450	beql	2f			# 	let turintr handle it
4513:
452	rsb
4532:
454	movab	_tudata,r4		# r4 = tudata
455	cmpb	$1,(r4)			# if (tudata.pk_flag != TUF_DATA)
456	bneq	3b			# 	let turintr handle it
4571:					# else
458	movl	24(r5),r1		# get buffer pointer to r1
459	movzbl	1(r4),r3		# counter to r3
460	movzwl	(r4),r0			# first word of checksum (=header)
461	mtpr	$0,$CSRS		# disable receiver interrupts
4623:
463	bsbw	5f			# wait for next byte
464	mfpr	$CSRD,r5
465	movb	r5,(r1)+		# *buffer = rdb
466	sobgtr	r3,1f			# continue with next byte ...
467	mfpr	$CSRD,r2		# unless this was the last (odd count)
468	brb	2f
469
4701:	bsbw	5f			# wait for next byte
471	mfpr	$CSRD,r5
472	movb	r5,(r1)+		# *buffer = rdb
473	movzwl	-2(r1),r2		# get the last word back from memory
4742:
475	addw2	r2,r0			# add to checksum..
476	adwc	$0,r0			# get the carry
477	sobgtr	r3,3b			# loop while r3 > 0
478/*
479 * We're ready to get the checksum.
480 */
481	bsbw	5f
482	movab	_tudata,r4
483	mfpr	$CSRD,r5
484	movb	r5,12(r4)		# get first (lower) byte
485	bsbw	5f
486	mfpr	$CSRD,r5
487	movb	r5,13(r4)		# ..and second
488	movab	_tu,r5
489	cmpw	12(r4),r0		# is checksum ok?
490	beql	1f
491	movl	$14,16(r5)		# tu.tu_state = TUS_CHKERR
492	brb	2f			# exit
4931:
494	movl	$11,16(r5)		# tu.tu_state = TUS_GET
4952:
496	mtpr	$0x40,$CSRS		# enable receiver interrupts
497	rsb				# continue processing in turintr
498/*
499 * Loop until a new byte is ready from
500 * the tu58, make sure we don't loop forever
501 */
5025:
503	movl	$5000,r5		# loop max 5000 times
5041:
505	mfpr	$CSRS,r2
506	bbs	$7,r2,1f
507	sobgtr	r5,1b
508	movab	_tu,r5
509	movl	$13,16(r5)		# return TUS_RCVERR
510	tstl	(sp)+			# and let turintr handle it
5111:
512	rsb
513#endif
514
515/*
516 * Stray UNIBUS interrupt catch routines
517 */
518	.data
519	.align	2
520#define	PJ	PUSHR;jsb _Xustray
521	.globl	_catcher
522_catcher:
523	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
524	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
525	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
526	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
527	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
528	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
529	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
530	PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ;PJ
531
532	.globl	_cold
533_cold:	.long	1
534	.data
535
536	.text
537SCBVEC(ustray):
538	blbc	_cold,1f
539	mfpr	$IPL,r11
540	subl3	$_catcher+8,(sp)+,r10
541	ashl	$-1,r10,r10
542	POPR
543	rei
5441:
545	subl3	$_catcher+8,(sp)+,r0
546	ashl	$-1,r0,-(sp)
547	mfpr	$IPL,-(sp)
548	PRINTF(2, "uba?: stray intr ipl %x vec %o\n")
549	POPR
550	rei
551
552#ifdef VAX630
553/*
554 * Emulation OpCode jump table:
555 *	ONLY GOES FROM 0xf8 (-8) TO 0x3B (59)
556 */
557#define EMUTABLE	0x43
558#define NOEMULATE	.long noemulate
559#define	EMULATE(a)	.long _EM/**/a
560	.globl	_emJUMPtable
561_emJUMPtable:
562/* f8 */	EMULATE(ashp);	EMULATE(cvtlp);	NOEMULATE;	NOEMULATE
563/* fc */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
564/* 00 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
565/* 04 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
566/* 08 */	EMULATE(cvtps);	EMULATE(cvtsp);	NOEMULATE;	EMULATE(crc)
567/* 0c */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
568/* 10 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
569/* 14 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
570/* 18 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
571/* 1c */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
572/* 20 */	EMULATE(addp4);	EMULATE(addp6);	EMULATE(subp4);	EMULATE(subp6)
573/* 24 */	EMULATE(cvtpt);	EMULATE(mulp);	EMULATE(cvttp);	EMULATE(divp)
574/* 28 */	NOEMULATE;	EMULATE(cmpc3);	EMULATE(scanc);	EMULATE(spanc)
575/* 2c */	NOEMULATE;	EMULATE(cmpc5);	EMULATE(movtc);	EMULATE(movtuc)
576/* 30 */	NOEMULATE;	NOEMULATE;	NOEMULATE;	NOEMULATE
577/* 34 */	EMULATE(movp);	EMULATE(cmpp3);	EMULATE(cvtpl);	EMULATE(cmpp4)
578/* 38 */	EMULATE(editpc); EMULATE(matchc); EMULATE(locc); EMULATE(skpc)
579#endif
580
581/*
582 * Trap and fault vector routines
583 */
584#define	TRAP(a)	pushl $T_/**/a; jbr alltraps
585
586/*
587 * Ast delivery (profiling and/or reschedule)
588 */
589SCBVEC(astflt):
590	pushl $0; TRAP(ASTFLT)
591SCBVEC(privinflt):
592	pushl $0; TRAP(PRIVINFLT)
593SCBVEC(xfcflt):
594	pushl $0; TRAP(XFCFLT)
595SCBVEC(resopflt):
596	pushl $0; TRAP(RESOPFLT)
597SCBVEC(resadflt):
598	pushl $0; TRAP(RESADFLT)
599SCBVEC(bptflt):
600	pushl $0; TRAP(BPTFLT)
601SCBVEC(compatflt):
602	TRAP(COMPATFLT);
603SCBVEC(kdbintr):
604	pushl $0; TRAP(KDBTRAP);
605SCBVEC(tracep):
606	pushl $0; TRAP(TRCTRAP)
607SCBVEC(arithtrap):
608	TRAP(ARITHTRAP)
609SCBVEC(protflt):
610	blbs	(sp)+,segflt
611	TRAP(PROTFLT)
612segflt:
613	TRAP(SEGFLT)
614
615/*
616 * The following is called with the stack set up as follows:
617 *
618 *	  (sp):	Opcode
619 *	 4(sp):	Instruction PC
620 *	 8(sp):	Operand 1
621 *	12(sp):	Operand 2
622 *	16(sp):	Operand 3
623 *	20(sp):	Operand 4
624 *	24(sp):	Operand 5
625 *	28(sp):	Operand 6
626 *	32(sp):	Operand 7 (unused)
627 *	36(sp):	Operand 8 (unused)
628 *	40(sp):	Return PC
629 *	44(sp):	Return PSL
630 *	48(sp): TOS before instruction
631 *
632 * Each individual routine is called with the stack set up as follows:
633 *
634 *	  (sp):	Return address of trap handler
635 *	 4(sp):	Opcode (will get return PSL)
636 *	 8(sp):	Instruction PC
637 *	12(sp):	Operand 1
638 *	16(sp):	Operand 2
639 *	20(sp):	Operand 3
640 *	24(sp):	Operand 4
641 *	28(sp):	Operand 5
642 *	32(sp):	Operand 6
643 *	36(sp):	saved register 11
644 *	40(sp):	saved register 10
645 *	44(sp):	Return PC
646 *	48(sp):	Return PSL
647 *	52(sp): TOS before instruction
648 */
649
650SCBVEC(emulate):
651#ifdef VAX630
652	movl	r11,32(sp)		# save register r11 in unused operand
653	movl	r10,36(sp)		# save register r10 in unused operand
654	cvtbl	(sp),r10		# get opcode
655	addl2	$8,r10			# shift negative opcodes
656	subl3	r10,$EMUTABLE,r11	# forget it if opcode is out of range
657	bcs	noemulate
658	movl	_emJUMPtable[r10],r10	# call appropriate emulation routine
659	jsb	(r10)		# routines put return values into regs 0-5
660	movl	32(sp),r11		# restore register r11
661	movl	36(sp),r10		# restore register r10
662	insv	(sp),$0,$4,44(sp)	# and condition codes in Opcode spot
663	addl2	$40,sp			# adjust stack for return
664	rei
665noemulate:
666	addl2	$48,sp			# adjust stack for
667#endif VAX630
668	.word	0xffff			# "reserved instruction fault"
669SCBVEC(emulateFPD):
670	.word	0xffff			# "reserved instruction fault"
671SCBVEC(transflt):
672	bitl	$2,(sp)+
673	bnequ	tableflt
674 	jsb	Fastreclaim		# try and avoid pagein
675	TRAP(PAGEFLT)
676tableflt:
677	TRAP(TABLEFLT)
678
679alltraps:
680	mfpr	$USP,-(sp); calls $0,_trap; mtpr (sp)+,$USP
681	incl	_cnt+V_TRAP
682	addl2	$8,sp			# pop type, code
683	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
684	rei
685
686SCBVEC(syscall):
687	pushl	$T_SYSCALL
688	mfpr	$USP,-(sp); calls $0,_syscall; mtpr (sp)+,$USP
689	incl	_cnt+V_SYSCALL
690	addl2	$8,sp			# pop type, code
691	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
692	rei
693
694/*
695 * System page table
696 * Mbmap and Usrptmap are enlarged by CLSIZE entries
697 * as they are managed by resource maps starting with index 1 or CLSIZE.
698 */
699#define	vaddr(x)	((((x)-_Sysmap)/4)*NBPG+0x80000000)
700#define	SYSMAP(mname, vname, npte)			\
701_/**/mname:	.globl	_/**/mname;		\
702	.space	(npte)*4;				\
703	.globl	_/**/vname;			\
704	.set	_/**/vname,vaddr(_/**/mname)
705
706	.data
707	.align	2
708	SYSMAP(Sysmap	,Sysbase	,SYSPTSIZE	)
709	SYSMAP(Forkmap	,forkutl	,UPAGES		)
710	SYSMAP(Xswapmap	,xswaputl	,UPAGES		)
711	SYSMAP(Xswap2map,xswap2utl	,UPAGES		)
712	SYSMAP(Swapmap	,swaputl	,UPAGES		)
713	SYSMAP(Pushmap	,pushutl	,UPAGES		)
714	SYSMAP(Vfmap	,vfutl		,UPAGES		)
715	SYSMAP(CMAP1	,CADDR1		,1		)
716	SYSMAP(CMAP2	,CADDR2		,1		)
717	SYSMAP(mmap	,vmmap		,1		)
718	SYSMAP(alignmap	,alignutl	,1		)	/* XXX */
719	SYSMAP(msgbufmap,msgbuf		,MSGBUFPTECNT	)
720	SYSMAP(Mbmap	,mbutl		,NMBCLUSTERS*CLSIZE+CLSIZE )
721	SYSMAP(kmempt	,kmembase	,100*CLSIZE	)
722#ifdef	GPROF
723	SYSMAP(profmap	,profbase	,600*CLSIZE	)
724#endif
725	SYSMAP(ekmempt	,kmemlimit	,0		)
726
727	SYSMAP(UMBAbeg	,umbabeg	,0		)
728	SYSMAP(Nexmap	,nexus		,16*MAXNNEXUS	)
729	SYSMAP(UMEMmap	,umem		,(UBAPAGES+UBAIOPAGES)*NUBA	)
730#if VAX8600
731	SYSMAP(Ioamap	,ioa		,MAXNIOA*IOAMAPSIZ/NBPG	)
732#endif
733#if VAX630
734	SYSMAP(Clockmap	,cldevice	,1		)
735	SYSMAP(Ka630map	,ka630cpu	,1		)
736	/*
737	 * qvss and qdss can't coexist - one map will suffice
738	 * for either. qvss is 256K each and qdss is 64K each.
739	 */
740#include "qv.h"
741#include "qd.h"
742#if NQV > 0 || NQD > 0
743	SYSMAP(QVmap	,qvmem		,((512*NQV)+(128*NQD)))
744#endif /* NQV || NQD */
745#endif /* VAX630 */
746	SYSMAP(UMBAend	,umbaend	,0		)
747
748	SYSMAP(Usrptmap	,usrpt		,USRPTSIZE+CLSIZE )
749
750eSysmap:
751	.globl	_Syssize
752	.set	_Syssize,(eSysmap-_Sysmap)/4
753	.text
754
755/*
756 * Initialization
757 *
758 * ipl 0x1f; mapen 0; scbb, pcbb, sbr, slr, isp, ksp not set
759 */
760	.data
761	.globl	_cpu
762_cpu:	.long	0
763	.text
764	.globl	start
765start:
766	.word	0
767	mtpr	$0,$ICCS
768/* set system control block base and system page table params */
769	mtpr	$_scb-0x80000000,$SCBB
770	mtpr	$_Sysmap-0x80000000,$SBR
771	mtpr	$_Syssize,$SLR
772/* double map the kernel into the virtual user addresses of phys mem */
773	mtpr	$_Sysmap,$P0BR
774	mtpr	$_Syssize,$P0LR
775/* set ISP and get cpu type */
776	movl	$_intstack+NISP*NBPG,sp
777	mfpr	$SID,r0
778	movab	_cpu,r1
779	extzv	$24,$8,r0,(r1)
780/* init RPB */
781	movab	_rpb,r0
782	movl	r0,(r0)+			# rp_selfref
783	movab	_doadump,r1
784	movl	r1,(r0)+			# rp_dumprout
785	movl	$0x1f,r2
786	clrl	r3
7871:	addl2	(r1)+,r3; sobgtr r2,1b
788	movl	r3,(r0)+			# rp_chksum
789/* count up memory */
790	clrl	r7
7911:	pushl	$4; pushl r7; calls $2,_badaddr; tstl r0; bneq 9f
792	acbl	$MAXMEM*1024-1,$64*1024,r7,1b
7939:
794#ifdef  VAX630
795/* leave an area for uVAX II console scratch pad at the top */
796	cmpb	_cpu,$VAX_630
797	bneq	1f
798	subl2   $4096,r7
7991:
800#endif
801/* clear memory from kernel bss and pages for proc 0 u. and page table */
802	movab	_edata,r6; bicl2 $SYSTEM,r6
803	movab	_end,r5; bicl2 $SYSTEM,r5
804#ifdef KDB
805	subl2	$4,r5
8061:	clrl	(r6); acbl r5,$4,r6,1b		# clear just bss
807	addl2	$4,r5
808	bbc	$6,r11,0f			# check RB_KDB
809	bicl3	$SYSTEM,r9,r5			# skip symbol & string tables
810	bicl3	$SYSTEM,r9,r6
811#endif
8120:	bisl3	$SYSTEM,r5,r9			# convert to virtual address
813	addl2	$NBPG-1,r9			# roundup to next page
814	addl2	$(UPAGES*NBPG)+NBPG+NBPG,r5
8151:	clrq	(r6); acbl r5,$8,r6,1b
816/* trap() and syscall() save r0-r11 in the entry mask (per ../h/reg.h) */
817/* panic() is convenient place to save all for debugging */
818	bisw2	$0x0fff,_trap
819	bisw2	$0x0fff,_syscall
820	bisw2	$0x0fff,_panic
821	calls	$0,_fixctlrmask
822/* initialize system page table: uba vectors and int stack writeable */
823	clrl	r2
824	movab	eintstack,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
8251:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
826/* make rpb, scb read-only as red zone for interrupt stack */
827	bicl2	$PG_PROT,_rpbmap
828	bisl2	$PG_KR,_rpbmap
829/* make kernel text space read-only */
830	movab	_etext+NBPG-1,r1; bbcc $31,r1,0f; 0: ashl $-PGSHIFT,r1,r1
8311:	bisl3	$PG_V|PG_URKR,r2,_Sysmap[r2]; aoblss r1,r2,1b
832/* make kernel data, bss, read-write */
833	bicl3	$SYSTEM,r9,r1; ashl $-PGSHIFT,r1,r1
8341:	bisl3	$PG_V|PG_KW,r2,_Sysmap[r2]; aoblss r1,r2,1b
835/* now go to mapped mode */
836	mtpr	$0,$TBIA; mtpr $1,$MAPEN; jmp *$0f; 0:
837/* init mem sizes */
838	ashl	$-PGSHIFT,r7,_maxmem
839	movl	_maxmem,_physmem
840	movl	_maxmem,_freemem
841/* setup context for proc[0] == Scheduler */
842	bicl3	$SYSTEM,r9,r6
843	bicl2	$NBPG-1,r6		# make page boundary
844/* setup page table for proc[0] */
845	ashl	$-PGSHIFT,r6,r3			# r3 = btoc(r6)
846	bisl3	$PG_V|PG_KW,r3,_Usrptmap	# init first upt entry
847	incl	r3
848	movab	_usrpt,r0
849	mtpr	r0,$TBIS
850/* init p0br, p0lr */
851	mtpr	r0,$P0BR
852	mtpr	$0,$P0LR
853/* init p1br, p1lr */
854	movab	NBPG(r0),r0
855	movl	$0x200000-UPAGES,r1
856	mtpr	r1,$P1LR
857	mnegl	r1,r1
858	moval	-4*UPAGES(r0)[r1],r2
859	mtpr	r2,$P1BR
860/* setup mapping for UPAGES of _u */
861	movl	$UPAGES,r2; movab _u+NBPG*UPAGES,r1; addl2 $UPAGES,r3; jbr 2f
8621:	decl	r3
863	moval	-NBPG(r1),r1;
864	bisl3	$PG_V|PG_URKW,r3,-(r0)
865	mtpr	r1,$TBIS
8662:	sobgeq	r2,1b
867/* initialize (slightly) the pcb */
868	movab	UPAGES*NBPG(r1),PCB_KSP(r1)
869	mnegl	$1,PCB_ESP(r1)
870	mnegl	$1,PCB_SSP(r1)
871	movl	r1,PCB_USP(r1)
872	mfpr	$P0BR,PCB_P0BR(r1)
873	mfpr	$P0LR,PCB_P0LR(r1)
874	movb	$4,PCB_P0LR+3(r1)		# disable ast
875	mfpr	$P1BR,PCB_P1BR(r1)
876	mfpr	$P1LR,PCB_P1LR(r1)
877	movl	$CLSIZE,PCB_SZPT(r1)		# init u.u_pcb.pcb_szpt
878	movl	r9,PCB_R9(r1)			# r9 obtained from boot
879	movl	r10,PCB_R10(r1)
880	movl	r11,PCB_R11(r1)
881	movab	1f,PCB_PC(r1)			# initial pc
882	clrl	PCB_PSL(r1)			# mode(k,k), ipl=0
883	ashl	$PGSHIFT,r3,r3
884	mtpr	r3,$PCBB			# first pcbb
885/* set regs, p0br, p0lr, p1br, p1lr, astlvl, ksp and change to kernel mode */
886	ldpctx
887	rei
888/* put signal trampoline code in u. area */
8891:	movab	_u,r0
890	movc3	$19,sigcode,PCB_SIGC(r0)
891/* save boot device in global _bootdev */
892	movl	r10,_bootdev
893/* save reboot flags in global _boothowto */
894	movl	r11,_boothowto
895/* save end of symbol & string table in global _bootesym */
896	subl3	$NBPG-1,r9,_bootesym
897/* calculate firstaddr, and call main() */
898	bicl3	$SYSTEM,r9,r0; ashl $-PGSHIFT,r0,-(sp)
899	addl2	$UPAGES+1,(sp); calls $1,_main
900/* proc[1] == /etc/init now running here; run icode */
901	pushl	$PSL_CURMOD|PSL_PRVMOD; pushl $0; rei
902
903/* signal trampoline code: it is known that this code takes exactly 19 bytes */
904/* in ../vax/pcb.h and in the movc3 above */
905sigcode:
906	calls	$4,8(pc)	# params pushed by sendsig
907	movl	sp,ap		# calls frame built by sendsig
908	chmk	$103		# cleanup mask and onsigstack
909	halt			# sigreturn() does not return!
910	.word	0x3f		# registers 0-5
911	callg	(ap),*16(ap)	# call the signal handler
912	ret			# return to code above
913
914	.set	exec,11
915	.set	exit,1
916	.globl	_icode
917	.globl	_initflags
918	.globl	_szicode
919/*
920 * Icode is copied out to process 1 to exec /etc/init.
921 * If the exec fails, process 1 exits.
922 */
923_icode:
924	pushab	b`argv-l0(pc)
925l0:	pushab	b`init-l1(pc)
926l1:	pushl	$2
927	movl	sp,ap
928	chmk	$exec
929	pushl	r0
930	chmk	$exit
931
932init:	.asciz	"/etc/init"
933	.align	2
934_initflags:
935	.long	0
936argv:	.long	init+5-_icode
937	.long	_initflags-_icode
938	.long	0
939_szicode:
940	.long	_szicode-_icode
941
942/*
943 * Primitives
944 */
945
946#ifdef GPROF
947#define	ENTRY(name, regs) \
948	.globl _/**/name; .align 1; _/**/name: .word regs; jsb mcount
949#define	JSBENTRY(name, regs) \
950	.globl _/**/name; _/**/name: \
951	movl fp,-(sp); movab -12(sp),fp; pushr $(regs); jsb mcount; \
952	popr $(regs); movl (sp)+,fp
953#else
954#define	ENTRY(name, regs) \
955	.globl _/**/name; .align 1; _/**/name: .word regs
956#define	JSBENTRY(name, regs) \
957	.globl _/**/name; _/**/name:
958#endif GPROF
959#define R0 0x01
960#define R1 0x02
961#define R2 0x04
962#define R3 0x08
963#define R4 0x10
964#define R5 0x20
965#define R6 0x40
966
967/*
968 * badaddr(addr, len)
969 *	see if access addr with a len type instruction causes a machine check
970 *	len is length of access (1=byte, 2=short, 4=long)
971 */
972	.globl	_badaddr
973_badaddr:
974	.word	0
975	movl	$1,r0
976	mfpr	$IPL,r1
977	mtpr	$HIGH,$IPL
978	movl	4(ap),r3
979	movl	8(ap),r4
980	movab	2f,nofault		# jump to 2f on machcheck
981	bbc	$0,r4,1f; tstb	(r3)
9821:	bbc	$1,r4,1f; tstw	(r3)
9831:	bbc	$2,r4,1f; tstl	(r3)
9841:	clrl	r0			# made it w/o machine checks
9852:	clrl	nofault
986	mtpr	r1,$IPL
987	ret
988
989/*
990 * update profiling information for the user
991 * addupc(pc, &u.u_prof, ticks)
992 */
993ENTRY(addupc, 0)
994	movl	8(ap),r2		# &u.u_prof
995	subl3	8(r2),4(ap),r0		# corrected pc
996	blss	9f
997	extzv	$1,$31,r0,r0		# logical right shift
998	extzv	$1,$31,12(r2),r1	# ditto for scale
999	emul	r1,r0,$0,r0
1000	ashq	$-14,r0,r0
1001	tstl	r1
1002	bneq	9f
1003	bicl2	$1,r0
1004	cmpl	r0,4(r2)		# length
1005	bgequ	9f
1006	addl2	(r2),r0			# base
1007	probew	$3,$2,(r0)
1008	beql	8f
1009	addw2	12(ap),(r0)
10109:
1011	ret
10128:
1013	clrl	12(r2)
1014	ret
1015
1016/*
1017 * Copy a null terminated string from the user address space into
1018 * the kernel address space.
1019 *
1020 * copyinstr(fromaddr, toaddr, maxlength, &lencopied)
1021 */
1022ENTRY(copyinstr, R6)
1023	movl	12(ap),r6		# r6 = max length
1024	jlss	8f
1025	movl	4(ap),r1		# r1 = user address
1026	bicl3	$~(NBPG*CLSIZE-1),r1,r2	# r2 = bytes on first page
1027	subl3	r2,$NBPG*CLSIZE,r2
1028	movl	8(ap),r3		# r3 = kernel address
10291:
1030	cmpl	r6,r2			# r2 = min(bytes on page, length left);
1031	jgeq	2f
1032	movl	r6,r2
10332:
1034	prober	$3,r2,(r1)		# bytes accessible?
1035	jeql	8f
1036	subl2	r2,r6			# update bytes left count
1037#ifdef NOSUBSINST
1038	# fake the locc instr. for processors that don't have it
1039	movl	r2,r0
10406:
1041	tstb	(r1)+
1042	jeql	5f
1043	sobgtr	r0,6b
1044	jbr	7f
10455:
1046	decl	r1
1047	jbr	3f
10487:
1049#else
1050	locc	$0,r2,(r1)		# null byte found?
1051	jneq	3f
1052#endif
1053	subl2	r2,r1			# back up pointer updated by `locc'
1054	movc3	r2,(r1),(r3)		# copy in next piece
1055	movl	$(NBPG*CLSIZE),r2	# check next page
1056	tstl	r6			# run out of space?
1057	jneq	1b
1058	movl	$ENOENT,r0		# set error code and return
1059	jbr	9f
10603:
1061	tstl	16(ap)			# return length?
1062	beql	4f
1063	subl3	r6,12(ap),r6		# actual len = maxlen - unused pages
1064	subl2	r0,r6			#	- unused on this page
1065	addl3	$1,r6,*16(ap)		#	+ the null byte
10664:
1067	subl2	r0,r2			# r2 = number of bytes to move
1068	subl2	r2,r1			# back up pointer updated by `locc'
1069	incl	r2			# copy null byte as well
1070	movc3	r2,(r1),(r3)		# copy in last piece
1071	clrl	r0			# redundant
1072	ret
10738:
1074	movl	$EFAULT,r0
10759:
1076	tstl	16(ap)
1077	beql	1f
1078	subl3	r6,12(ap),*16(ap)
10791:
1080	ret
1081
1082/*
1083 * Copy a null terminated string from the kernel
1084 * address space to the user address space.
1085 *
1086 * copyoutstr(fromaddr, toaddr, maxlength, &lencopied)
1087 */
1088ENTRY(copyoutstr, R6)
1089	movl	12(ap),r6		# r6 = max length
1090	jlss	8b
1091	movl	4(ap),r1		# r1 = kernel address
1092	movl	8(ap),r3		# r3 = user address
1093	bicl3	$~(NBPG*CLSIZE-1),r3,r2	# r2 = bytes on first page
1094	subl3	r2,$NBPG*CLSIZE,r2
10951:
1096	cmpl	r6,r2			# r2 = min(bytes on page, length left);
1097	jgeq	2f
1098	movl	r6,r2
10992:
1100	probew	$3,r2,(r3)		# bytes accessible?
1101	jeql	8b
1102	subl2	r2,r6			# update bytes left count
1103#ifdef NOSUBSINST
1104	# fake the locc instr. for processors that don't have it
1105	movl	r2,r0
11066:
1107	tstb	(r1)+
1108	jeql	5f
1109	sobgtr	r0,6b
1110	jbr	7f
11115:
1112	decl	r1
1113	jbr	3b
11147:
1115#else
1116	locc	$0,r2,(r1)		# null byte found?
1117	jneq	3b
1118#endif
1119	subl2	r2,r1			# back up pointer updated by `locc'
1120	movc3	r2,(r1),(r3)		# copy in next piece
1121	movl	$(NBPG*CLSIZE),r2	# check next page
1122	tstl	r6			# run out of space?
1123	jneq	1b
1124	movl	$ENOENT,r0		# set error code and return
1125	jbr	9b
1126
1127/*
1128 * Copy a null terminated string from one point to another in
1129 * the kernel address space.
1130 *
1131 * copystr(fromaddr, toaddr, maxlength, &lencopied)
1132 */
1133ENTRY(copystr, R6)
1134	movl	12(ap),r6		# r6 = max length
1135	jlss	8b
1136	movl	4(ap),r1		# r1 = src address
1137	movl	8(ap),r3		# r3 = dest address
11381:
1139	movzwl	$65535,r2		# r2 = bytes in first chunk
1140	cmpl	r6,r2			# r2 = min(bytes in chunk, length left);
1141	jgeq	2f
1142	movl	r6,r2
11432:
1144	subl2	r2,r6			# update bytes left count
1145#ifdef NOSUBSINST
1146	# fake the locc instr. for processors that don't have it
1147	movl	r2,r0
11486:
1149	tstb	(r1)+
1150	jeql	5f
1151	sobgtr	r0,6b
1152	jbr	7f
11535:
1154	decl	r1
1155	jbr	3b
11567:
1157#else
1158	locc	$0,r2,(r1)		# null byte found?
1159	jneq	3b
1160#endif
1161	subl2	r2,r1			# back up pointer updated by `locc'
1162	movc3	r2,(r1),(r3)		# copy in next piece
1163	tstl	r6			# run out of space?
1164	jneq	1b
1165	movl	$ENOENT,r0		# set error code and return
1166	jbr	9b
1167
1168/*
1169 * Copy specified amount of data from user space into the kernel
1170 * Copyin(from, to, len)
1171 *	r1 == from (user source address)
1172 *	r3 == to (kernel destination address)
1173 *	r5 == length
1174 */
1175	.align	1
1176JSBENTRY(Copyin, R1|R3|R5)
1177	cmpl	r5,$(NBPG*CLSIZE)	# probing one page or less ?
1178	bgtru	1f			# no
1179	prober	$3,r5,(r1)		# bytes accessible ?
1180	beql	ersb			# no
1181	movc3	r5,(r1),(r3)
1182/*	clrl	r0			# redundant */
1183	rsb
11841:
1185	blss	ersb			# negative length?
1186	pushl	r6			# r6 = length
1187	movl	r5,r6
1188	bicl3	$~(NBPG*CLSIZE-1),r1,r0	# r0 = bytes on first page
1189	subl3	r0,$(NBPG*CLSIZE),r0
1190	addl2	$(NBPG*CLSIZE),r0	# plus one additional full page
1191	jbr	2f
1192
1193ciloop:
1194	movc3	r0,(r1),(r3)
1195	movl	$(2*NBPG*CLSIZE),r0	# next amount to move
11962:
1197	cmpl	r0,r6
1198	bleq	3f
1199	movl	r6,r0
12003:
1201	prober	$3,r0,(r1)		# bytes accessible ?
1202	beql	ersb1			# no
1203	subl2	r0,r6			# last move?
1204	bneq	ciloop			# no
1205
1206	movc3	r0,(r1),(r3)
1207/*	clrl	r0			# redundant */
1208	movl	(sp)+,r6		# restore r6
1209	rsb
1210
1211ersb1:
1212	movl	(sp)+,r6		# restore r6
1213ersb:
1214	movl	$EFAULT,r0
1215	rsb
1216
1217/*
1218 * Copy specified amount of data from kernel to the user space
1219 * Copyout(from, to, len)
1220 *	r1 == from (kernel source address)
1221 *	r3 == to (user destination address)
1222 *	r5 == length
1223 */
1224	.align	1
1225JSBENTRY(Copyout, R1|R3|R5)
1226	cmpl	r5,$(NBPG*CLSIZE)	# moving one page or less ?
1227	bgtru	1f			# no
1228	probew	$3,r5,(r3)		# bytes writeable?
1229	beql	ersb			# no
1230	movc3	r5,(r1),(r3)
1231/*	clrl	r0			# redundant */
1232	rsb
12331:
1234	blss	ersb			# negative length?
1235	pushl	r6			# r6 = length
1236	movl	r5,r6
1237	bicl3	$~(NBPG*CLSIZE-1),r3,r0	# r0 = bytes on first page
1238	subl3	r0,$(NBPG*CLSIZE),r0
1239	addl2	$(NBPG*CLSIZE),r0	# plus one additional full page
1240	jbr	2f
1241
1242coloop:
1243	movc3	r0,(r1),(r3)
1244	movl	$(2*NBPG*CLSIZE),r0	# next amount to move
12452:
1246	cmpl	r0,r6
1247	bleq	3f
1248	movl	r6,r0
12493:
1250	probew	$3,r0,(r3)		# bytes writeable?
1251	beql	ersb1			# no
1252	subl2	r0,r6			# last move?
1253	bneq	coloop			# no
1254
1255	movc3	r0,(r1),(r3)
1256/*	clrl	r0			# redundant */
1257	movl	(sp)+,r6		# restore r6
1258	rsb
1259
1260/*
1261 * non-local goto's
1262 */
1263#ifdef notdef		/* this is now expanded completely inline */
1264	.align	1
1265JSBENTRY(Setjmp, R0)
1266	movl	fp,(r0)+	# current stack frame
1267	movl	(sp),(r0)	# resuming pc
1268	clrl	r0
1269	rsb
1270#endif
1271
1272#define PCLOC 16	/* location of pc in calls frame */
1273#define APLOC 8		/* location of ap,fp in calls frame */
1274	.align	1
1275JSBENTRY(Longjmp, R0)
1276	movl	(r0)+,newfp	# must save parameters in memory as all
1277	movl	(r0),newpc	# registers may be clobbered.
12781:
1279	cmpl	fp,newfp	# are we there yet?
1280	bgequ	2f		# yes
1281	moval	1b,PCLOC(fp)	# redirect return pc to us!
1282	ret			# pop next frame
12832:
1284	beql	3f		# did we miss our frame?
1285	pushab	4f		# yep ?!?
1286	calls	$1,_panic
12873:
1288	movl	newpc,r0	# all done, just return to the `setjmp'
1289	jmp	(r0)		# ``rsb''
1290
1291	.data
1292newpc:	.space	4
1293newfp:	.space	4
12944:	.asciz	"longjmp"
1295	.text
1296/*
1297 * setjmp that saves all registers as the call frame may not
1298 * be available to recover them in the usual mannor by longjmp.
1299 * Called before swapping out the u. area, restored by resume()
1300 * below.
1301 */
1302ENTRY(savectx, 0)
1303	movl	4(ap),r0
1304	movq	r6,(r0)+
1305	movq	r8,(r0)+
1306	movq	r10,(r0)+
1307	movq	APLOC(fp),(r0)+	# save ap, fp
1308	addl3	$8,ap,(r0)+	# save sp
1309	movl	PCLOC(fp),(r0)	# save pc
1310	clrl	r0
1311	ret
1312
1313#ifdef KDB
1314/*
1315 * C library -- reset, setexit
1316 *
1317 *	reset(x)
1318 * will generate a "return" from
1319 * the last call to
1320 *	setexit()
1321 * by restoring r6 - r12, ap, fp
1322 * and doing a return.
1323 * The returned value is x; on the original
1324 * call the returned value is 0.
1325 */
1326ENTRY(setexit)
1327	movab	setsav,r0
1328	movq	r6,(r0)+
1329	movq	r8,(r0)+
1330	movq	r10,(r0)+
1331	movq	8(fp),(r0)+		# ap, fp
1332	movab	4(ap),(r0)+		# sp
1333	movl	16(fp),(r0)		# pc
1334	clrl	r0
1335	ret
1336
1337ENTRY(reset)
1338	movl	4(ap),r0	# returned value
1339	movab	setsav,r1
1340	movq	(r1)+,r6
1341	movq	(r1)+,r8
1342	movq	(r1)+,r10
1343	movq	(r1)+,r12
1344	movl	(r1)+,sp
1345	jmp 	*(r1)
1346
1347	.data
1348	.align  2
1349setsav:	.space	10*4
1350	.text
1351#endif
1352
1353	.globl	_whichqs
1354	.globl	_qs
1355	.globl	_cnt
1356
1357	.globl	_noproc
1358	.comm	_noproc,4
1359	.globl	_runrun
1360	.comm	_runrun,4
1361
1362/*
1363 * The following primitives use the fancy VAX instructions
1364 * much like VMS does.  _whichqs tells which of the 32 queues _qs
1365 * have processes in them.  Setrq puts processes into queues, Remrq
1366 * removes them from queues.  The running process is on no queue,
1367 * other processes are on a queue related to p->p_pri, divided by 4
1368 * actually to shrink the 0-127 range of priorities into the 32 available
1369 * queues.
1370 */
1371
1372/*
1373 * Setrq(p), using fancy VAX instructions.
1374 *
1375 * Call should be made at splclock(), and p->p_stat should be SRUN
1376 */
1377	.align	1
1378JSBENTRY(Setrq, R0)
1379	tstl	P_RLINK(r0)		## firewall: p->p_rlink must be 0
1380	beql	set1			##
1381	pushab	set3			##
1382	calls	$1,_panic		##
1383set1:
1384	movzbl	P_PRI(r0),r1		# put on queue which is p->p_pri / 4
1385	ashl	$-2,r1,r1
1386	movaq	_qs[r1],r2
1387	insque	(r0),*4(r2)		# at end of queue
1388	bbss	r1,_whichqs,set2	# mark queue non-empty
1389set2:
1390	rsb
1391
1392set3:	.asciz	"setrq"
1393
1394/*
1395 * Remrq(p), using fancy VAX instructions
1396 *
1397 * Call should be made at splclock().
1398 */
1399	.align	1
1400JSBENTRY(Remrq, R0)
1401	movzbl	P_PRI(r0),r1
1402	ashl	$-2,r1,r1
1403	bbsc	r1,_whichqs,rem1
1404	pushab	rem3			# it wasn't recorded to be on its q
1405	calls	$1,_panic
1406rem1:
1407	remque	(r0),r2
1408	beql	rem2
1409	bbss	r1,_whichqs,rem2
1410rem2:
1411	clrl	P_RLINK(r0)		## for firewall checking
1412	rsb
1413
1414rem3:	.asciz	"remrq"
1415
1416/*
1417 * Masterpaddr is the p->p_addr of the running process on the master
1418 * processor.  When a multiprocessor system, the slave processors will have
1419 * an array of slavepaddr's.
1420 */
1421	.globl	_masterpaddr
1422	.data
1423_masterpaddr:
1424	.long	0
1425
1426	.text
1427sw0:	.asciz	"swtch"
1428
1429/*
1430 * When no processes are on the runq, Swtch branches to idle
1431 * to wait for something to come ready.
1432 */
1433	.globl	Idle
1434Idle: idle:
1435	movl	$1,_noproc
1436	mtpr	$0,$IPL			# must allow interrupts here
14371:
1438	tstl	_whichqs		# look for non-empty queue
1439	bneq	sw1
1440	brb	1b
1441
1442badsw:	pushab	sw0
1443	calls	$1,_panic
1444	/*NOTREACHED*/
1445
1446/*
1447 * Swtch(), using fancy VAX instructions
1448 */
1449	.align	1
1450JSBENTRY(Swtch, 0)
1451	incl	_cnt+V_SWTCH
1452sw1:	ffs	$0,$32,_whichqs,r0	# look for non-empty queue
1453	beql	idle			# if none, idle
1454	mtpr	$0x18,$IPL		# lock out all so _whichqs==_qs
1455	bbcc	r0,_whichqs,sw1		# proc moved via interrupt
1456	movaq	_qs[r0],r1
1457	remque	*(r1),r2		# r2 = p = highest pri process
1458	bvs	badsw			# make sure something was there
1459	beql	sw2
1460	insv	$1,r0,$1,_whichqs	# still more procs in this queue
1461sw2:
1462	clrl	_noproc
1463	clrl	_runrun
1464#ifdef notdef
1465	tstl	P_WCHAN(r2)		## firewalls
1466	bneq	badsw			##
1467	cmpb	P_STAT(r2),$SRUN	##
1468	bneq	badsw			##
1469#endif
1470	clrl	P_RLINK(r2)		##
1471	movl	*P_ADDR(r2),r0
1472#ifdef notdef
1473	cmpl	r0,_masterpaddr		# resume of current proc is easy
1474	beql	res0
1475#endif
1476	movl	r0,_masterpaddr
1477	ashl	$PGSHIFT,r0,r0		# r0 = pcbb(p)
1478/* fall into... */
1479
1480/*
1481 * Resume(pf)
1482 */
1483JSBENTRY(Resume, R0)
1484	mtpr	$HIGH,$IPL			# no interrupts, please
1485	movl	_CMAP2,_u+PCB_CMAP2	# yech
1486	svpctx
1487	mtpr	r0,$PCBB
1488	ldpctx
1489	movl	_u+PCB_CMAP2,_CMAP2	# yech
1490	mtpr	$_CADDR2,$TBIS
1491res0:
1492	tstl	_u+PCB_SSWAP
1493	bneq	res1
1494	rei
1495res1:
1496	movl	_u+PCB_SSWAP,r0			# longjmp to saved context
1497	clrl	_u+PCB_SSWAP
1498	movq	(r0)+,r6
1499	movq	(r0)+,r8
1500	movq	(r0)+,r10
1501	movq	(r0)+,r12
1502	movl	(r0)+,r1
1503	cmpl	r1,sp				# must be a pop
1504	bgequ	1f
1505	pushab	2f
1506	calls	$1,_panic
1507	/* NOTREACHED */
15081:
1509	movl	r1,sp
1510	movl	(r0),(sp)			# address to return to
1511	movl	$PSL_PRVMOD,4(sp)		# ``cheating'' (jfr)
1512	rei
1513
15142:	.asciz	"ldctx"
1515
1516/*
1517 * {fu,su},{byte,word}, all massaged by asm.sed to jsb's
1518 */
1519	.align	1
1520JSBENTRY(Fuword, R0)
1521	prober	$3,$4,(r0)
1522	beql	fserr
1523	movl	(r0),r0
1524	rsb
1525fserr:
1526	mnegl	$1,r0
1527	rsb
1528
1529	.align	1
1530JSBENTRY(Fubyte, R0)
1531	prober	$3,$1,(r0)
1532	beql	fserr
1533	movzbl	(r0),r0
1534	rsb
1535
1536	.align	1
1537JSBENTRY(Suword, R0|R1)
1538	probew	$3,$4,(r0)
1539	beql	fserr
1540	movl	r1,(r0)
1541	clrl	r0
1542	rsb
1543
1544	.align	1
1545JSBENTRY(Subyte, R0|R1)
1546	probew	$3,$1,(r0)
1547	beql	fserr
1548	movb	r1,(r0)
1549	clrl	r0
1550	rsb
1551
1552/*
1553 * Copy 1 relocation unit (NBPG bytes)
1554 * from user virtual address to physical address
1555 */
1556ENTRY(copyseg, 0)
1557	bisl3	$PG_V|PG_KW,8(ap),_CMAP2
1558	mtpr	$_CADDR2,$TBIS	# invalidate entry for copy
1559	movc3	$NBPG,*4(ap),_CADDR2
1560	ret
1561
1562/*
1563 * zero out physical memory
1564 * specified in relocation units (NBPG bytes)
1565 */
1566ENTRY(clearseg, 0)
1567	bisl3	$PG_V|PG_KW,4(ap),_CMAP1
1568	mtpr	$_CADDR1,$TBIS
1569	movc5	$0,(sp),$0,$NBPG,_CADDR1
1570	ret
1571
1572/*
1573 * Check address.
1574 * Given virtual address, byte count, and rw flag
1575 * returns 0 on no access.
1576 */
1577ENTRY(useracc, 0)
1578	movl	4(ap),r0		# get va
1579	movl	8(ap),r1		# count
1580	tstl	12(ap)			# test for read access ?
1581	bneq	userar			# yes
1582	cmpl	$NBPG,r1			# can we do it in one probe ?
1583	bgeq	uaw2			# yes
1584uaw1:
1585	probew	$3,$NBPG,(r0)
1586	beql	uaerr			# no access
1587	addl2	$NBPG,r0
1588	acbl	$NBPG+1,$-NBPG,r1,uaw1
1589uaw2:
1590	probew	$3,r1,(r0)
1591	beql	uaerr
1592	movl	$1,r0
1593	ret
1594
1595userar:
1596	cmpl	$NBPG,r1
1597	bgeq	uar2
1598uar1:
1599	prober	$3,$NBPG,(r0)
1600	beql	uaerr
1601	addl2	$NBPG,r0
1602	acbl	$NBPG+1,$-NBPG,r1,uar1
1603uar2:
1604	prober	$3,r1,(r0)
1605	beql	uaerr
1606	movl	$1,r0
1607	ret
1608uaerr:
1609	clrl	r0
1610	ret
1611
1612/*
1613 * kernacc - check for kernel access privileges
1614 *
1615 * We can't use the probe instruction directly because
1616 * it ors together current and previous mode.
1617 */
1618 ENTRY(kernacc, 0)
1619	movl	4(ap),r0	# virtual address
1620	bbcc	$31,r0,kacc1
1621	bbs	$30,r0,kacerr
1622	mfpr	$SBR,r2		# address and length of page table (system)
1623	bbss	$31,r2,0f; 0:
1624	mfpr	$SLR,r3
1625	brb	kacc2
1626kacc1:
1627	bbsc	$30,r0,kacc3
1628	mfpr	$P0BR,r2	# user P0
1629	mfpr	$P0LR,r3
1630	brb	kacc2
1631kacc3:
1632	mfpr	$P1BR,r2	# user P1 (stack)
1633	mfpr	$P1LR,r3
1634kacc2:
1635	addl3	8(ap),r0,r1	# ending virtual address
1636	addl2	$NBPG-1,r1
1637	ashl	$-PGSHIFT,r0,r0
1638	ashl	$-PGSHIFT,r1,r1
1639	bbs	$31,4(ap),kacc6
1640	bbc	$30,4(ap),kacc6
1641	cmpl	r0,r3		# user stack
1642	blss	kacerr		# address too low
1643	brb	kacc4
1644kacc6:
1645	cmpl	r1,r3		# compare last page to P0LR or SLR
1646	bgtr	kacerr		# address too high
1647kacc4:
1648	movl	(r2)[r0],r3
1649	bbc	$31,4(ap),kacc4a
1650	bbc	$31,r3,kacerr	# valid bit is off
1651kacc4a:
1652	cmpzv	$27,$4,r3,$1	# check protection code
1653	bleq	kacerr		# no access allowed
1654	tstb	12(ap)
1655	bneq	kacc5		# only check read access
1656	cmpzv	$27,$2,r3,$3	# check low 2 bits of prot code
1657	beql	kacerr		# no write access
1658kacc5:
1659	aoblss	r1,r0,kacc4	# next page
1660	movl	$1,r0		# no errors
1661	ret
1662kacerr:
1663	clrl	r0		# error
1664	ret
1665/*
1666 * Extracted and unrolled most common case of pagein (hopefully):
1667 *	resident and not on free list (reclaim of page is purely
1668 *	for the purpose of simulating a reference bit)
1669 *
1670 * Built in constants:
1671 *	CLSIZE of 2, any bit fields in pte's
1672 */
1673	.text
1674	.globl	Fastreclaim
1675Fastreclaim:
1676	PUSHR
1677#ifdef GPROF
1678	movl	fp,-(sp)
1679	movab	12(sp),fp
1680	jsb	mcount
1681	movl	(sp)+,fp
1682#endif GPROF
1683	extzv	$9,$23,28(sp),r3	# virtual address
1684	bicl2	$1,r3			# v = clbase(btop(virtaddr));
1685	movl	_u+U_PROCP,r5		# p = u.u_procp
1686					# from vtopte(p, v) ...
1687	movl	$1,r2			# type = CTEXT;
1688	cmpl	r3,P_TSIZE(r5)
1689	jlssu	1f			# if (isatsv(p, v)) {
1690	addl3	P_TSIZE(r5),P_DSIZE(r5),r0
1691	cmpl	r3,r0
1692	jgequ	2f
1693	clrl	r2			#	type = !CTEXT;
16941:
1695	ashl	$2,r3,r4
1696	addl2	P_P0BR(r5),r4		#	tptopte(p, vtotp(p, v));
1697	jbr	3f
16982:
1699	cvtwl	P_SZPT(r5),r4		# } else (isassv(p, v)) {
1700	ashl	$7,r4,r4
1701	subl2	$0x400000,r4
1702	addl2	r3,r4
1703	ashl	$2,r4,r4
1704	addl2	P_P0BR(r5),r4		#	sptopte(p, vtosp(p, v));
1705	clrl	r2			# 	type = !CTEXT;
17063:					# }
1707	bitb	$0x82,3(r4)
1708	beql	2f			# if (pte->pg_v || pte->pg_fod)
1709	POPR; rsb			#	let pagein handle it
17102:
1711	bicl3	$0xffe00000,(r4),r0
1712	jneq	2f			# if (pte->pg_pfnum == 0)
1713	POPR; rsb			# 	let pagein handle it
17142:
1715	subl2	_firstfree,r0
1716	ashl	$-1,r0,r0
1717	incl	r0			# pgtocm(pte->pg_pfnum)
1718	mull2	$SZ_CMAP,r0
1719	addl2	_cmap,r0		# &cmap[pgtocm(pte->pg_pfnum)]
1720	tstl	r2
1721	jeql	2f			# if (type == CTEXT &&
1722	jbc	$C_INTRANS,(r0),2f	#     c_intrans)
1723	POPR; rsb			# 	let pagein handle it
17242:
1725	jbc	$C_FREE,(r0),2f		# if (c_free)
1726	POPR; rsb			# 	let pagein handle it
17272:
1728	bisb2	$0x80,3(r4)		# pte->pg_v = 1;
1729	jbc	$26,4(r4),2f		# if (anycl(pte, pg_m)
1730	bisb2	$0x04,3(r4)		#	pte->pg_m = 1;
17312:
1732	bicw3	$0x7f,2(r4),r0
1733	bicw3	$0xff80,6(r4),r1
1734	bisw3	r0,r1,6(r4)		# distcl(pte);
1735	ashl	$PGSHIFT,r3,r0
1736	mtpr	r0,$TBIS
1737	addl2	$NBPG,r0
1738	mtpr	r0,$TBIS		# tbiscl(v);
1739	tstl	r2
1740	jeql	2f			# if (type == CTEXT)
1741	movl	P_TEXTP(r5),r0
1742	movl	X_CADDR(r0),r5		# for (p = p->p_textp->x_caddr; p; ) {
1743	jeql	2f
1744	ashl	$2,r3,r3
17453:
1746	addl3	P_P0BR(r5),r3,r0	#	tpte = tptopte(p, tp);
1747	bisb2	$1,P_FLAG+3(r5)		#	p->p_flag |= SPTECHG;
1748	movl	(r4),(r0)+		#	for (i = 0; i < CLSIZE; i++)
1749	movl	4(r4),(r0)		#		tpte[i] = pte[i];
1750	movl	P_XLINK(r5),r5		#	p = p->p_xlink;
1751	jneq	3b			# }
17522:					# collect a few statistics...
1753	incl	_u+U_RU+RU_MINFLT	# u.u_ru.ru_minflt++;
1754	moval	_cnt,r0
1755	incl	V_FAULTS(r0)		# cnt.v_faults++;
1756	incl	V_PGREC(r0)		# cnt.v_pgrec++;
1757	incl	V_FASTPGREC(r0)		# cnt.v_fastpgrec++;
1758	incl	V_TRAP(r0)		# cnt.v_trap++;
1759	POPR
1760	addl2	$8,sp			# pop pc, code
1761	mtpr	$HIGH,$IPL		## dont go to a higher IPL (GROT)
1762	rei
1763