xref: /original-bsd/sys/hp300/hp300/locore.s (revision ba762ddc)
1/*
2 * Copyright (c) 1988 University of Utah.
3 * Copyright (c) 1980, 1990 The Regents of the University of California.
4 * All rights reserved.
5 *
6 * This code is derived from software contributed to Berkeley by
7 * the Systems Programming Group of the University of Utah Computer
8 * Science Department.
9 *
10 * %sccs.include.redist.c%
11 *
12 * from: Utah $Hdr: locore.s 1.2 90/07/14$
13 *
14 *	@(#)locore.s	7.8 (Berkeley) 05/01/91
15 */
16
17#include "assym.s"
18#include "vectors.s"
19
20#define MMUADDR(ar)	movl	_MMUbase,ar
21#define CLKADDR(ar)	movl	_CLKbase,ar
22
23	.text
24/*
25 * This is where we wind up if the kernel jumps to location 0.
26 * (i.e. a bogus PC)  This is known to immediately follow the vector
27 * table and is hence at 0x400 (see reset vector in vectors.s).
28 */
29	.globl	_panic
30	pea	Ljmp0panic
31	jbsr	_panic
32	/* NOTREACHED */
33Ljmp0panic:
34	.asciz	"kernel jump to zero"
35	.even
36
37/*
38 * Do a dump.
39 * Called by auto-restart.
40 */
41	.globl	_dumpsys
42	.globl	_doadump
43_doadump:
44	jbsr	_dumpsys
45	jbsr	_doboot
46	/*NOTREACHED*/
47
48/*
49 * Trap/interrupt vector routines
50 */
51
52	.globl	_trap, _nofault, _longjmp
53_buserr:
54	tstl	_nofault		| device probe?
55	jeq	_addrerr		| no, handle as usual
56	movl	_nofault,sp@-		| yes,
57	jbsr	_longjmp		|  longjmp(nofault)
58_addrerr:
59	clrw	sp@-			| pad SR to longword
60	moveml	#0xFFFF,sp@-		| save user registers
61	movl	usp,a0			| save the user SP
62	movl	a0,sp@(60)		|   in the savearea
63	lea	sp@(64),a1		| grab base of HW berr frame
64	movw	a1@(12),d0		| grab SSW for fault processing
65	btst	#12,d0			| RB set?
66	jeq	LbeX0			| no, test RC
67	bset	#14,d0			| yes, must set FB
68	movw	d0,a1@(12)		| for hardware too
69LbeX0:
70	btst	#13,d0			| RC set?
71	jeq	LbeX1			| no, skip
72	bset	#15,d0			| yes, must set FC
73	movw	d0,a1@(12)		| for hardware too
74LbeX1:
75	btst	#8,d0			| data fault?
76	jeq	Lbe0			| no, check for hard cases
77	movl	a1@(18),d1		| fault address is as given in frame
78	jra	Lbe10			| thats it
79Lbe0:
80	btst	#4,a1@(8)		| long (type B) stack frame?
81	jne	Lbe4			| yes, go handle
82	movl	a1@(4),d1		| no, can use save PC
83	btst	#14,d0			| FB set?
84	jeq	Lbe3			| no, try FC
85	addql	#4,d1			| yes, adjust address
86	jra	Lbe10			| done
87Lbe3:
88	btst	#15,d0			| FC set?
89	jeq	Lbe10			| no, done
90	addql	#2,d1			| yes, adjust address
91	jra	Lbe10			| done
92Lbe4:
93	movl	a1@(38),d1		| long format, use stage B address
94	btst	#15,d0			| FC set?
95	jeq	Lbe10			| no, all done
96	subql	#2,d1			| yes, adjust address
97Lbe10:
98	movl	d1,sp@-			| push fault VA
99	movw	d0,sp@-			| and SSW
100	clrw	sp@-			|   padded to longword
101	movw	a1@(8),d0		| get frame format/vector offset
102	andw	#0x0FFF,d0		| clear out frame format
103	cmpw	#12,d0			| address error vector?
104	jeq	Lisaerr			| yes, go to it
105#if defined(HP330) || defined(HP360) || defined(HP370)
106	tstl	_mmutype		| HP MMU?
107	jeq	Lbehpmmu		| yes, skip
108	movl	d1,a0			| fault address
109	ptestr	#1,a0@,#7		| do a table search
110	pmove	psr,sp@			| save result
111	btst	#7,sp@			| bus error bit set?
112	jeq	Lismerr			| no, must be MMU fault
113	clrw	sp@			| yes, re-clear pad word
114	jra	Lisberr			| and process as normal bus error
115Lbehpmmu:
116#endif
117#if defined(HP320) || defined(HP350)
118	MMUADDR(a0)
119	movl	a0@(MMUSTAT),d0		| read status
120	btst	#3,d0			| MMU fault?
121	jeq	Lisberr			| no, just a non-MMU bus error so skip
122	andl	#~MMU_FAULT,a0@(MMUSTAT)| yes, clear fault bits
123	movw	d0,sp@			| pass MMU stat in upper half of code
124#endif
125Lismerr:
126	movl	#T_MMUFLT,sp@-		| show that we are an MMU fault
127	jra	Lbexit			| and deal with it
128Lisaerr:
129	movl	#T_ADDRERR,sp@-		| mark address error
130	jra	Lbexit			| and deal with it
131Lisberr:
132	movl	#T_BUSERR,sp@-		| mark bus error
133Lbexit:
134	jbsr	_trap			| handle the error
135	lea	sp@(12),sp		| pop value args
136	movl	sp@(60),a0		| restore user SP
137	movl	a0,usp			|   from save area
138	moveml	sp@+,#0x7FFF		| restore most user regs
139	addql	#4,sp			| toss SSP
140	tstw	sp@+			| do we need to clean up stack?
141	jeq	rei			| no, just continue
142	btst	#7,sp@(6)		| type 9/10/11 frame?
143	jeq	rei			| no, nothing to do
144	btst	#5,sp@(6)		| type 9?
145	jne	Lbex1			| no, skip
146	movw	sp@,sp@(12)		| yes, push down SR
147	movl	sp@(2),sp@(14)		| and PC
148	clrw	sp@(18)			| and mark as type 0 frame
149	lea	sp@(12),sp		| clean the excess
150	jra	rei			| all done
151Lbex1:
152	btst	#4,sp@(6)		| type 10?
153	jne	Lbex2			| no, skip
154	movw	sp@,sp@(24)		| yes, push down SR
155	movl	sp@(2),sp@(26)		| and PC
156	clrw	sp@(30)			| and mark as type 0 frame
157	lea	sp@(24),sp		| clean the excess
158	jra	rei			| all done
159Lbex2:
160	movw	sp@,sp@(84)		| type 11, push down SR
161	movl	sp@(2),sp@(86)		| and PC
162	clrw	sp@(90)			| and mark as type 0 frame
163	lea	sp@(84),sp		| clean the excess
164	jra	rei			| all done
165
166_illinst:
167	clrw	sp@-
168	moveml	#0xFFFF,sp@-
169	moveq	#T_ILLINST,d0
170	jra	_fault
171
172_zerodiv:
173	clrw	sp@-
174	moveml	#0xFFFF,sp@-
175	moveq	#T_ZERODIV,d0
176	jra	_fault
177
178_chkinst:
179	clrw	sp@-
180	moveml	#0xFFFF,sp@-
181	moveq	#T_CHKINST,d0
182	jra	_fault
183
184_trapvinst:
185	clrw	sp@-
186	moveml	#0xFFFF,sp@-
187	moveq	#T_TRAPVINST,d0
188	jra	_fault
189
190_privinst:
191	clrw	sp@-
192	moveml	#0xFFFF,sp@-
193	moveq	#T_PRIVINST,d0
194	jra	_fault
195
196_coperr:
197	clrw	sp@-
198	moveml	#0xFFFF,sp@-
199	moveq	#T_COPERR,d0
200	jra	_fault
201
202_fmterr:
203	clrw	sp@-
204	moveml	#0xFFFF,sp@-
205	moveq	#T_FMTERR,d0
206	jra	_fault
207
208_fptrap:
209#ifdef FPCOPROC
210	clrw	sp@-		| pad SR to longword
211	moveml	#0xFFFF,sp@-	| save user registers
212	movl	usp,a0		| and save
213	movl	a0,sp@(60)	|   the user stack pointer
214	clrl	sp@-		| no VA arg
215	movl	_masterpaddr,a0	| current pcb
216	lea	a0@(PCB_FPCTX),a0 | address of FP savearea
217	fsave	a0@		| save state
218	tstb	a0@		| null state frame?
219	jeq	Lfptnull	| yes, safe
220	clrw	d0		| no, need to tweak BIU
221	movb	a0@(1),d0	| get frame size
222	bset	#3,a0@(0,d0:w)	| set exc_pend bit of BIU
223Lfptnull:
224	fmovem	fpsr,sp@-	| push fpsr as code argument
225	frestore a0@		| restore state
226	movl	#T_FPERR,sp@-	| push type arg
227	jbsr	_trap		| call trap
228	lea	sp@(12),sp	| pop value args
229	movl	sp@(60),a0	| restore
230	movl	a0,usp		|   user SP
231	moveml	sp@+,#0x7FFF	| and remaining user registers
232	addql	#6,sp		| pop SSP and align word
233	jra	rei		| all done
234#else
235	jra	_badtrap	| treat as an unexpected trap
236#endif
237
238	.globl	_fault
239_fault:
240	movl	usp,a0		| get and save
241	movl	a0,sp@(60)	|   the user stack pointer
242	clrl	sp@-		| no VA arg
243	clrl	sp@-		| or code arg
244	movl	d0,sp@-		| push trap type
245	jbsr	_trap		| handle trap
246	lea	sp@(12),sp	| pop value args
247	movl	sp@(60),a0	| restore
248	movl	a0,usp		|   user SP
249	moveml	sp@+,#0x7FFF	| restore most user regs
250	addql	#6,sp		| pop SP and pad word
251	jra	rei		| all done
252
253	.globl	_straytrap
254_badtrap:
255	clrw	sp@-
256	moveml	#0xC0C0,sp@-
257	movw	sp@(24),sp@-
258	clrw	sp@-
259	jbsr	_straytrap
260	addql	#4,sp
261	moveml	sp@+,#0x0303
262	addql	#2,sp
263	jra	rei
264
265	.globl	_syscall
266_trap0:
267	clrw	sp@-			| pad SR to longword
268	moveml	#0xFFFF,sp@-		| save user registers
269	movl	usp,a0			| save the user SP
270	movl	a0,sp@(60)		|   in the savearea
271	movl	d0,sp@-			| push syscall number
272	jbsr	_syscall		| handle it
273	addql	#4,sp			| pop syscall arg
274	movl	sp@(60),a0		| grab and restore
275	movl	a0,usp			|   user SP
276	moveml	sp@+,#0x7FFF		| restore most registers
277	addql	#6,sp			| pop SSP and align word
278	jra	rei			| all done
279
280/*
281 * Routines for traps 1 and 2.  The meaning of the two traps depends
282 * on whether we are an HPUX compatible process or a native 4.3 process.
283 * Our native 4.3 implementation uses trap 1 as sigreturn() and trap 2
284 * as a breakpoint trap.  HPUX uses trap 1 for a breakpoint, so we have
285 * to make adjustments so that trap 2 is used for sigreturn.
286 */
287_trap1:
288	btst	#PCB_TRCB,pcbflag	| being traced by an HPUX process?
289	jeq	sigreturn		| no, trap1 is sigreturn
290	jra	_trace			| yes, trap1 is breakpoint
291
292_trap2:
293	btst	#PCB_TRCB,pcbflag	| being traced by an HPUX process?
294	jeq	_trace			| no, trap2 is breakpoint
295	jra	sigreturn		| yes, trap2 is sigreturn
296
297/*
298 * Trap 15 is used for:
299 *	- KGDB traps
300 *	- trace traps for SUN binaries (not fully supported yet)
301 * We just pass it on and let trap() sort it all out
302 */
303	.globl	_kgdb_trap_glue
304_trap15:
305	clrw	sp@-
306	moveml	#0xFFFF,sp@-
307#ifdef KGDB
308	moveq	#T_TRAP15,d0
309	movl	sp@(64),d1		| from user mode?
310	andl	#PSL_S,d1
311	jeq	_fault
312	movl	d0,sp@-
313	jbsr	_kgdb_trap_glue		| returns if no debugger
314	addl	#4,sp
315#endif
316	moveq	#T_TRAP15,d0
317	jra	_fault
318
319/*
320 * Hit a breakpoint (trap 1 or 2) instruction.
321 * Push the code and treat as a normal fault.
322 */
323_trace:
324	clrw	sp@-
325	moveml	#0xFFFF,sp@-
326#ifdef KGDB
327	moveq	#T_TRACE,d0
328	movl	sp@(64),d1		| from user mode?
329	andl	#PSL_S,d1
330	jeq	_fault
331	movl	d0,sp@-
332	jbsr	_kgdb_trap_glue		| returns if no debugger
333	addl	#4,sp
334#endif
335	moveq	#T_TRACE,d0
336	jra	_fault
337
338/*
339 * The sigreturn() syscall comes here.  It requires special handling
340 * because we must open a hole in the stack to fill in the (possibly much
341 * larger) original stack frame.
342 */
343sigreturn:
344	lea	sp@(-84),sp		| leave enough space for largest frame
345	movl	sp@(84),sp@		| move up current 8 byte frame
346	movl	sp@(88),sp@(4)
347	movw	#0xFFFF,sp@-		| default: must clean stack
348	moveml	#0xFFFF,sp@-		| save user registers
349	movl	usp,a0			| save the user SP
350	movl	a0,sp@(60)		|   in the savearea
351	movl	#SYS_sigreturn,sp@-	| push syscall number
352	jbsr	_syscall		| handle it
353	addql	#4,sp			| pop syscall#
354	movl	sp@(60),a0		| grab and restore
355	movl	a0,usp			|   user SP
356	lea	sp@(64),a1		| pointer to HW frame
357	tstw	a1@+			| do we need to clean up stack?
358	jeq	Lsigr1			| no, just continue
359	movb	a1@(6),d0		| grab format byte
360	lsrb	#4,d0			| get rid of excess
361	cmpb	#10,d0			| type 10 frame?
362	jne	Lsigr2			| no, continue
363	movw	#32,d1			| yes, frame size is 32 bytes
364	jra	Lsigrcp			| go to it
365Lsigr2:
366	cmpb	#9,d0			| type 9?
367	jne	Lsigr3			| no, continue
368	movw	#20,d1			| yes, frame size is 20 bytes
369	jra	Lsigrcp			| go to it
370Lsigr3:
371	cmpb	#2,d0			| type 2?
372	jne	Lsigr4			| no, continue
373	movw	#12,d1			| yes, frame size is 12 bytes
374	jra	Lsigrcp			| go to it
375Lsigr4:
376	movw	#8,d1			| must be type 0/1, size is 8 bytes
377Lsigrcp:
378	lea	a1@(92),a0		| destination
379	addw	d1,a1			| source
380	lsrw	#1,d1			| convert to word count
381	subqw	#1,d1			| minus 1 for dbf
382Lsigrlp:
383	movw	a1@-,a0@-		| copy a word
384	dbf	d1,Lsigrlp		| continue
385	movl	a0,a1			| new HW frame base
386Lsigr1:
387	movl	a1,sp@(60)		| new SP value
388	moveml	sp@+,#0x7FFF		| restore user registers
389	movl	sp@,sp			| and our SP
390	jra	rei			| all done
391
392/*
393 * Interrupt handlers.
394 * All DIO device interrupts are auto-vectored.  Most can be configured
395 * to interrupt in the range IPL3 to IPL5.  Here are our assignments:
396 *
397 *	Level 0:	Spurious: ignored.
398 *	Level 1:	HIL
399 *	Level 2:
400 *	Level 3:	Internal HP-IB
401 *	Level 4:	"Fast" HP-IBs, SCSI
402 *	Level 5:	DMA, Ethernet, Built-in RS232
403 *	Level 6:	Clock
404 *	Level 7:	Non-maskable: parity errors, RESET key
405 */
406	.globl	_hilint, _intrhand, _hardclock, _nmihand
407
408_spurintr:
409	addql	#1,_intrcnt+0
410	addql	#1,_cnt+V_INTR
411	jra	rei
412
413_lev1intr:
414	addql	#1,_intrcnt+4
415	clrw	sp@-
416	moveml	#0xC0C0,sp@-
417	jbsr	_hilint
418	moveml	sp@+,#0x0303
419	addql	#2,sp
420	addql	#1,_cnt+V_INTR
421	jra	rei
422
423/* check for DMA first to reduce overhead */
424_lev5intr:
425	clrw	sp@-
426	moveml	#0xC0C0,sp@-
427	jbsr	_dmaintr
428	tstl	d0
429	jeq	Lnotdma
430	addql	#1,_intrcnt+24
431	moveml	sp@+,#0x0303
432	addql	#2,sp
433	addql	#1,_cnt+V_INTR
434	jra	rei
435
436_lev2intr:
437_lev3intr:
438_lev4intr:
439	clrw	sp@-
440	moveml	#0xC0C0,sp@-
441Lnotdma:
442	lea	_intrcnt,a0
443	movw	sp@(24),d0		| use vector offset
444	andw	#0xfff,d0		|   sans frame type
445	addql	#1,a0@(-0x60,d0:w)	|     to increment apropos counter
446	movw	sr,sp@-			| push current SR value
447	clrw	sp@-			|    padded to longword
448	jbsr	_intrhand		| handle interrupt
449	addql	#4,sp			| pop SR
450	moveml	sp@+,#0x0303
451	addql	#2,sp
452	addql	#1,_cnt+V_INTR
453	jra	rei
454
455_lev6intr:
456	clrw	sp@-
457	moveml	#0xC0C0,sp@-
458#ifdef DEBUG
459	.globl	_panicstr, _regdump, _panic
460	tstl	timebomb		| set to go off?
461	jeq	Lnobomb			| no, skip it
462	subql	#1,timebomb		| decrement
463	jne	Lnobomb			| not ready to go off
464	moveml	sp@+,#0x0303		| temporarily restore regs
465	jra	Luseours		| go die
466Lnobomb:
467	cmpl	#_kstack+NBPG,sp	| are we still in stack pages?
468	jcc	Lstackok		| yes, continue normally
469	tstl	_panicstr		| have we paniced?
470	jne	Lstackok		| yes, do not re-panic
471	lea	tmpstk,sp		| no, switch to tmpstk
472Luseours:
473	moveml	#0xFFFF,sp@-		| push all registers
474	movl	sp,a0			| remember this spot
475	movl	#256,sp@-		| longword count
476	movl	a0,sp@-			| and reg pointer
477	jbsr	_regdump		| dump core
478	addql	#8,sp			| pop params
479	movl	#Lstkrip,sp@-		| push panic message
480	jbsr	_panic			| ES and D
481Lstkrip:
482	.asciz	"k-stack overflow"
483	.even
484Lstackok:
485#endif
486	CLKADDR(a0)
487	movb	a0@(CLKSR),d0		| read clock status
488#ifdef PROFTIMER
489	.globl  _profon
490	tstb	_profon			| profile clock on?
491	jeq     Ltimer1			| no, then must be timer1 interrupt
492	btst	#2,d0			| timer3 interrupt?
493	jeq     Ltimer1			| no, must be timer1
494	movb	a0@(CLKMSB3),d1		| clear timer3 interrupt
495	lea	sp@(16),a1		| get pointer to PS
496#ifdef GPROF
497	.globl	_profclock
498	movl	d0,sp@-			| save status so jsr will not clobber
499	movl	a1@,sp@-		| push padded PS
500	movl	a1@(4),sp@-		| push PC
501	jbsr	_profclock		| profclock(pc, ps)
502	addql	#8,sp			| pop params
503#else
504	btst	#5,a1@(2)		| saved PS in user mode?
505	jne	Lttimer1		| no, go check timer1
506	movl	_masterpaddr,a0		| current pcb
507	tstl	a0@(U_PROFSCALE)	| process being profiled?
508	jeq	Lttimer1		| no, go check timer1
509	movl	d0,sp@-			| save status so jsr will not clobber
510	movl	#1,sp@-
511	pea	a0@(U_PROF)
512	movl	a1@(4),sp@-
513	jbsr    _addupc			| addupc(pc, &u.u_prof, 1)
514	lea	sp@(12),sp		| pop params
515#endif
516	addql	#1,_intrcnt+32		| add another profile clock interrupt
517	movl	sp@+,d0			| get saved clock status
518	CLKADDR(a0)
519Lttimer1:
520	btst	#0,d0			| timer1 interrupt?
521	jeq     Ltimend		        | no, check state of kernel profiling
522Ltimer1:
523#endif
524	movb	a0@(CLKMSB1),d1		| clear timer1 interrupt
525	lea	sp@(16),a1		| get pointer to PS
526	movl	a1@,sp@-		| push padded PS
527	movl	a1@(4),sp@-		| push PC
528	jbsr	_hardclock		| call generic clock int routine
529	addql	#8,sp			| pop params
530	addql	#1,_intrcnt+28		| add another system clock interrupt
531#ifdef PROFTIMER
532Ltimend:
533#ifdef GPROF
534	.globl	_profiling, _startprofclock
535	tstl	_profiling		| kernel profiling desired?
536	jne	Ltimdone		| no, all done
537	bset	#7,_profon		| mark continuous timing
538	jne	Ltimdone		| was already enabled, all done
539	jbsr	_startprofclock		| else turn it on
540Ltimdone:
541#endif
542#endif
543	moveml	sp@+,#0x0303		| restore scratch regs
544	addql	#2,sp			| pop pad word
545	addql	#1,_cnt+V_INTR		| chalk up another interrupt
546	jra	rei			| all done
547
548_lev7intr:
549#ifdef PROFTIMER
550	addql	#1,_intrcnt+36
551#else
552	addql	#1,_intrcnt+32
553#endif
554	clrw	sp@-			| pad SR to longword
555	moveml	#0xFFFF,sp@-		| save registers
556	movl	usp,a0			| and save
557	movl	a0,sp@(60)		|   the user stack pointer
558	jbsr	_nmihand		| call handler
559	movl	sp@(60),a0		| restore
560	movl	a0,usp			|   user SP
561	moveml	sp@+,#0x7FFF		| and remaining registers
562	addql	#6,sp			| pop SSP and align word
563	jra	rei			| all done
564
565/*
566 * Emulation of VAX REI instruction.
567 *
568 * This code deals with checking for and servicing ASTs
569 * (profiling, scheduling) and software interrupts (network, softclock).
570 * We check for ASTs first, just like the VAX.  To avoid excess overhead
571 * the T_ASTFLT handling code will also check for software interrupts so we
572 * do not have to do it here.
573 *
574 * This code is complicated by the fact that sendsig may have been called
575 * necessitating a stack cleanup.  A cleanup should only be needed at this
576 * point for coprocessor mid-instruction frames (type 9), but we also test
577 * for bus error frames (type 10 and 11).
578 */
579	.comm	_ssir,1
580	.globl	_astpending
581rei:
582#ifdef DEBUG
583	tstl	_panicstr		| have we paniced?
584	jne	Ldorte			| yes, do not make matters worse
585#endif
586	tstl	_astpending		| AST pending?
587	jeq	Lchksir			| no, go check for SIR
588	btst	#5,sp@			| yes, are we returning to user mode?
589	jne	Lchksir			| no, go check for SIR
590	clrw	sp@-			| pad SR to longword
591	moveml	#0xFFFF,sp@-		| save all registers
592	movl	usp,a1			| including
593	movl	a1,sp@(60)		|    the users SP
594	clrl	sp@-			| VA == none
595	clrl	sp@-			| code == none
596	movl	#T_ASTFLT,sp@-		| type == async system trap
597	jbsr	_trap			| go handle it
598	lea	sp@(12),sp		| pop value args
599	movl	sp@(60),a0		| restore
600	movl	a0,usp			|   user SP
601	moveml	sp@+,#0x7FFF		| and all remaining registers
602	addql	#4,sp			| toss SSP
603	tstw	sp@+			| do we need to clean up stack?
604	jeq	Ldorte			| no, just continue
605	btst	#7,sp@(6)		| type 9/10/11 frame?
606	jeq	Ldorte			| no, nothing to do
607	btst	#5,sp@(6)		| type 9?
608	jne	Last1			| no, skip
609	movw	sp@,sp@(12)		| yes, push down SR
610	movl	sp@(2),sp@(14)		| and PC
611	clrw	sp@(18)			| and mark as type 0 frame
612	lea	sp@(12),sp		| clean the excess
613	jra	Ldorte			| all done
614Last1:
615	btst	#4,sp@(6)		| type 10?
616	jne	Last2			| no, skip
617	movw	sp@,sp@(24)		| yes, push down SR
618	movl	sp@(2),sp@(26)		| and PC
619	clrw	sp@(30)			| and mark as type 0 frame
620	lea	sp@(24),sp		| clean the excess
621	jra	Ldorte			| all done
622Last2:
623	movw	sp@,sp@(84)		| type 11, push down SR
624	movl	sp@(2),sp@(86)		| and PC
625	clrw	sp@(90)			| and mark as type 0 frame
626	lea	sp@(84),sp		| clean the excess
627	jra	Ldorte			| all done
628Lchksir:
629	tstb	_ssir			| SIR pending?
630	jeq	Ldorte			| no, all done
631	movl	d0,sp@-			| need a scratch register
632	movw	sp@(4),d0		| get SR
633	andw	#PSL_IPL7,d0		| mask all but IPL
634	jne	Lnosir			| came from interrupt, no can do
635	movl	sp@+,d0			| restore scratch register
636Lgotsir:
637	movw	#SPL1,sr		| prevent others from servicing int
638	tstb	_ssir			| too late?
639	jeq	Ldorte			| yes, oh well...
640	clrw	sp@-			| pad SR to longword
641	moveml	#0xFFFF,sp@-		| save all registers
642	movl	usp,a1			| including
643	movl	a1,sp@(60)		|    the users SP
644	clrl	sp@-			| VA == none
645	clrl	sp@-			| code == none
646	movl	#T_SSIR,sp@-		| type == software interrupt
647	jbsr	_trap			| go handle it
648	lea	sp@(12),sp		| pop value args
649	movl	sp@(60),a0		| restore
650	movl	a0,usp			|   user SP
651	moveml	sp@+,#0x7FFF		| and all remaining registers
652	addql	#6,sp			| pop SSP and align word
653	rte
654Lnosir:
655	movl	sp@+,d0			| restore scratch register
656Ldorte:
657	rte				| real return
658
659/*
660 * Kernel access to the current processes kernel stack is via a fixed
661 * virtual address.  It is at the same address as in the users VA space.
662 * Umap contains the KVA of the first of UPAGES PTEs mapping VA _kstack.
663 */
664	.data
665	.set	_kstack,USRSTACK
666_Umap:	.long	0
667	.globl	_kstack, _Umap
668
669#define	RELOC(var, ar)	\
670	lea	var,ar;	\
671	addl	a5,ar
672
673/*
674 * Initialization
675 *
676 * A5 contains physical load point from boot
677 * VBR contains zero from ROM.  Exceptions will continue to vector
678 * through ROM until MMU is turned on at which time they will vector
679 * through our table (vectors.s).
680 */
681	.comm	_lowram,4
682
683	.text
684	.globl	_edata
685	.globl	_etext,_end
686	.globl	start
687start:
688	movw	#PSL_HIGHIPL,sr		| no interrupts
689	RELOC(tmpstk, a0)
690	movl	a0,sp			| give ourselves a temporary stack
691	RELOC(_lowram, a0)
692	movl	a5,a0@			| store start of physical memory
693	movl	#CACHE_OFF,d0
694	movc	d0,cacr			| clear and disable on-chip cache(s)
695
696/* determine our CPU/MMU combo - check for all regardless of kernel config */
697	movl	#IOBASE+MMUBASE,a1
698	movl	#0x200,d0		| data freeze bit
699	movc	d0,cacr			|   only exists on 68030
700	movc	cacr,d0			| read it back
701	tstl	d0			| zero?
702	jeq	Lis68020		| yes, we have 68020
703	RELOC(_mmutype, a0)		| no, we have 68030
704	movl	#-1,a0@			| set to reflect 68030 PMMU
705	RELOC(_machineid, a0)
706	movl	#0x80,a1@(MMUCMD)	| set magic cookie
707	movl	a1@(MMUCMD),d0		| read it back
708	btst	#7,d0			| cookie still on?
709	jeq	Lnot370			| no, 360 or 375
710	movl	#0,a1@(MMUCMD)		| clear magic cookie
711	movl	a1@(MMUCMD),d0		| read it back
712	btst	#7,d0			| still on?
713	jeq	Lisa370			| no, must be a 370
714	movl	#5,a0@			| yes, must be a 340
715	jra	Lstart1
716Lnot370:
717	movl	#3,a0@			| type is at least a 360
718	movl	#0,a1@(MMUCMD)		| clear magic cookie2
719	movl	a1@(MMUCMD),d0		| read it back
720	btst	#16,d0			| still on?
721	jeq	Lstart1			| no, must be a 360
722	movl	#6,a0@			| yes, must be a 345/375
723	jra	Lhaspac
724Lisa370:
725	movl	#4,a0@			| set to 370
726Lhaspac:
727	RELOC(_ectype, a0)
728	movl	#-1,a0@			| also has a physical address cache
729	jra	Lstart1
730Lis68020:
731	movl	#1,a1@(MMUCMD)		| a 68020, write HP MMU location
732	movl	a1@(MMUCMD),d0		| read it back
733	btst	#0,d0			| non-zero?
734	jne	Lishpmmu		| yes, we have HP MMU
735	RELOC(_mmutype, a0)
736	movl	#1,a0@			| no, we have PMMU
737	RELOC(_machineid, a0)
738	movl	#1,a0@			| and 330 CPU
739	jra	Lstart1
740Lishpmmu:
741	RELOC(_ectype, a0)		| 320 or 350
742	movl	#1,a0@			| both have a virtual address cache
743	movl	#0x80,a1@(MMUCMD)	| set magic cookie
744	movl	a1@(MMUCMD),d0		| read it back
745	btst	#7,d0			| cookie still on?
746	jeq	Lstart1			| no, just a 320
747	RELOC(_machineid, a0)
748	movl	#2,a0@			| yes, a 350
749
750Lstart1:
751	movl	#0,a1@(MMUCMD)		| clear out MMU again
752/* initialize source/destination control registers for movs */
753	moveq	#FC_USERD,d0		| user space
754	movc	d0,sfc			|   as source
755	movc	d0,dfc			|   and destination of transfers
756
757/*
758 * Allocate kernel segment/page table resources.
759 *	a5 contains the PA of lowest RAM page
760 *	a4 contains the PA of first available page at any time
761 *	d5 contains the VA of first available page at any time
762 *	   (since we assume a zero load point, it is also the size of
763 *	   allocated space at any time)
764 * We assume (i.e. do not check) that the initial page table size
765 * (Sysptsize) is big enough to map everything we allocate here.
766 *
767 * We allocate the DIO map here since the 320/350 MMU registers are
768 * mapped in this range and it would be nice to be able to access them
769 * after the MMU is turned on.
770 */
771	.globl	_Sysseg, _Sysmap, _Sysptmap, _Sysptsize
772	movl	#_end,d5		| end of static kernel text/data
773	addl	#NBPG-1,d5
774	andl	#PG_FRAME,d5		| round to a page
775	movl	d5,a4
776	addl	a5,a4
777/* allocate kernel segment table */
778	RELOC(_Sysseg, a0)
779	movl	d5,a0@			| remember VA for pmap module
780	movl	a4,sp@-			| remember PA for loading MMU
781	addl	#NBPG,a4
782	addl	#NBPG,d5
783/* allocate initial page table pages (including IO map) */
784	RELOC(_Sysptsize, a0)
785	movl	a0@,d0			| initial system PT size (pages)
786	addl	#(IOMAPSIZE+NPTEPG-1)/NPTEPG,d0	| add pages for IO map
787	movl	#PGSHIFT,d1
788	lsll	d1,d0			| convert to bytes
789	movl	a4,sp@-			| remember PA for ST load
790	addl	d0,a4
791	addl	d0,d5
792/* allocate kernel page table map */
793	RELOC(_Sysptmap, a0)
794	movl	d5,a0@			| remember VA for pmap module
795	movl	a4,sp@-			| remember PA for PT map load
796	addl	#NBPG,a4
797	addl	#NBPG,d5
798/* compute KVA of Sysptmap; mapped after page table pages */
799	movl	d0,d2			| remember PT size (bytes)
800	moveq	#SG_ISHIFT-PGSHIFT,d1
801	lsll	d1,d0			| page table size serves as seg index
802	RELOC(_Sysmap, a0)
803	movl	d0,a0@			| remember VA for pmap module
804/* initialize ST and PT map: PT pages + PT map */
805	movl	sp@+,a1			| PT map PA
806	movl	sp@+,d4			| start of PT pages
807	movl	sp@+,a0			| ST phys addr
808	lea	a0@(NBPG-4),a2		| (almost) end of ST
809	movl	d4,d3
810	orl	#SG_RW+SG_V,d4		| create proto STE for ST
811	orl	#PG_RW+PG_CI+PG_V,d3	| create proto PTE for PT map
812List1:
813	movl	d4,a0@+
814	movl	d3,a1@+
815	addl	#NBPG,d4
816	addl	#NBPG,d3
817	cmpl	a4,d4			| sleezy, but works ok
818	jcs	List1
819/* initialize ST and PT map: invalidate up to last entry */
820List2:
821	movl	#SG_NV,a0@+
822	movl	#PG_NV,a1@+
823	cmpl	a2,a0
824	jcs	List2
825/*
826 * Portions of the last segment of KVA space (0xFFF00000 - 0xFFFFFFFF)
827 * are mapped for a couple of purposes. 0xFFF00000 for UPAGES is used
828 * for mapping the current process u-area (u + kernel stack).  The
829 * very last page (0xFFFFF000) is mapped to the last physical page of
830 * RAM to give us a region in which PA == VA.  We use this page for
831 * enabling/disabling mapping.
832 */
833	movl	a4,d1			| grab next available for PT page
834	andl	#SG_FRAME,d1		| mask to frame number
835	orl	#SG_RW+SG_V,d1		| RW and valid
836	movl	d1,a0@+			| store in last ST entry
837	movl	a0,a2			| remember addr for PT load
838	andl	#PG_FRAME,d1
839	orl	#PG_RW+PG_V,d1		| convert to PTE
840	movl	d1,a1@+			| store in PT map
841	movl	a4,a0			| physical beginning of PT page
842	lea	a0@(NBPG-4),a1		| (almost) end of page
843Lispt7:
844	movl	#PG_NV,a0@+		| invalidate
845	cmpl	a1,a0
846	jcs	Lispt7
847	movl	#MAXADDR,d1		| get last phys page addr
848	andl	#PG_FRAME,d1
849	orl	#PG_RW+PG_V,d1
850	movl	d1,a0@+			| map to last virt page
851	addl	#NBPG,a4
852	addl	#NBPG,d5
853/* record KVA at which to access current u-area PTEs */
854	RELOC(_Sysmap, a0)
855	movl	a0@,d0			| get system PT address
856	addl	#NPTEPG*NBPG,d0		| end of system PT
857	subl	#HIGHPAGES*4,d0		| back up to first PTE for u-area
858	RELOC(_Umap, a0)
859	movl	d0,a0@			| remember location
860/* initialize page table pages */
861	movl	a2,a0			| end of ST is start of PT
862	addl	d2,a2			| add size to get end of PT
863/* text pages are read-only */
864	clrl	d0			| assume load at VA 0
865	movl	a5,d1			| get load PA
866	andl	#PG_FRAME,d1		| convert to a page frame
867#ifdef KGDB
868	orl	#PG_RW+PG_V,d1		| XXX: RW for now
869#else
870	orl	#PG_RO+PG_V,d1		| create proto PTE
871#endif
872	movl	#_etext,a1		| go til end of text
873Lipt1:
874	movl	d1,a0@+			| load PTE
875	addl	#NBPG,d1		| increment page frame number
876	addl	#NBPG,d0		| and address counter
877	cmpl	a1,d0			| done yet?
878	jcs	Lipt1			| no, keep going
879/* data, bss and dynamic tables are read/write */
880	andl	#PG_FRAME,d1		| mask out old prot bits
881	orl	#PG_RW+PG_V,d1		| mark as valid and RW
882	movl	d5,a1			| go til end of data allocated so far
883	addl	#(UPAGES+1)*NBPG,a1	| and proc0 PT/u-area (to be allocated)
884Lipt2:
885	movl	d1,a0@+			| load PTE
886	addl	#NBPG,d1		| increment page frame number
887	addl	#NBPG,d0		| and address counter
888	cmpl	a1,d0			| done yet?
889	jcs	Lipt2			| no, keep going
890/* invalidate remainder of kernel PT */
891	movl	a2,a1			| end of PT
892Lipt3:
893	movl	#PG_NV,a0@+		| invalidate PTE
894	cmpl	a1,a0			| done yet?
895	jcs	Lipt3			| no, keep going
896/* go back and validate IO PTEs at end of allocated PT space */
897	movl	a2,a0			| end of allocated PT space
898	subl	#IOMAPSIZE*4,a0		| back up IOMAPSIZE PTEs
899	movl	#IOBASE,d1		| physical IO base
900	orl	#PG_RW+PG_CI+PG_V,d1	| create proto PTE
901Lipt4:
902	movl	d1,a0@+			| load PTE
903	addl	#NBPG,d1		| increment page frame number
904	cmpl	a2,a0			| done yet?
905	jcs	Lipt4			| no, keep going
906/* record base KVA of IO space which is just before Sysmap */
907	RELOC(_Sysmap, a0)
908	movl	a0@,d0			| Sysmap VA
909	subl	#IOMAPSIZE*NBPG,d0	| Back up size of IO space
910	RELOC(_DIObase, a0)
911	movl	d0,a0@
912/* also record base of clock and MMU registers for fast access */
913	addl	#CLKBASE,d0
914	RELOC(_CLKbase, a0)
915	movl	d0,a0@
916	subl	#CLKBASE,d0
917	addl	#MMUBASE,d0
918	RELOC(_MMUbase, a0)
919	movl	d0,a0@
920
921/*
922 * Setup page table for process 0.
923 *
924 * We set up page table access for the kernel via Usrptmap (usrpt)
925 * and access to the u-area itself via Umap (u).  First available
926 * page (VA: d5, PA: a4) is used for proc0 page table.  Next UPAGES
927 * pages following are for u-area.
928 */
929	movl	a4,d0
930	movl	d0,d1
931	andl	#PG_FRAME,d1		| mask to page frame number
932	orl	#PG_RW+PG_V,d1		| RW and valid
933	movl	d1,d4			| remember for later Usrptmap load
934	movl	d0,a0			| base of proc0 PT
935	addl	#NBPG,d0		| plus one page yields base of u-area
936	movl	d0,a2			|   and end of PT
937	addl	#NBPG,d5		| keep VA in sync
938/* invalidate entire page table */
939Liudot1:
940	movl	#PG_NV,a0@+		| invalidate PTE
941	cmpl	a2,a0			| done yet?
942	jcs	Liudot1			| no, keep going
943/* now go back and validate u-area PTEs in PT and in Umap */
944	lea	a0@(-HIGHPAGES*4),a0	| base of PTEs for u-area (p_addr)
945	lea	a0@(UPAGES*4),a1	| end of PTEs for u-area
946	lea	a4@(-HIGHPAGES*4),a3	| u-area PTE base in Umap PT
947	movl	d0,d1			| get base of u-area
948	andl	#PG_FRAME,d1		| mask to page frame number
949	orl	#PG_RW+PG_V,d1		| add valid and writable
950Liudot2:
951	movl	d1,a0@+			| validate p_addr PTE
952	movl	d1,a3@+			| validate u PTE
953	addl	#NBPG,d1		| to next page
954	cmpl	a1,a0			| done yet?
955	jcs	Liudot2			| no, keep going
956/* clear process 0 u-area */
957	addl	#NBPG*UPAGES,d0		| end of u-area
958Lclru1:
959	clrl	a2@+			| clear
960	cmpl	d0,a2			| done yet?
961	jcs	Lclru1			| no, keep going
962	movl	a2,a4			| save phys addr of first avail page
963	RELOC(_proc0paddr, a0)
964	movl	d5,a0@			| save KVA of proc0 u-area
965	addl	#UPAGES*NBPG,d5		| increment virtual addr as well
966
967/*
968 * Prepare to enable MMU.
969 * Since the kernel is not mapped logical == physical we must insure
970 * that when the MMU is turned on, all prefetched addresses (including
971 * the PC) are valid.  In order guarentee that, we use the last physical
972 * page (which is conveniently mapped == VA) and load it up with enough
973 * code to defeat the prefetch, then we execute the jump back to here.
974 *
975 * Is this all really necessary, or am I paranoid??
976 */
977	RELOC(_Sysseg, a0)		| system segment table addr
978	movl	a0@,a1			| read value (a KVA)
979	addl	a5,a1			| convert to PA
980	RELOC(_mmutype, a0)
981	tstl	a0@			| HP MMU?
982	jeq	Lhpmmu2			| yes, skip
983	RELOC(_protorp, a0)
984	movl	#0x80000202,a0@		| nolimit + share global + 4 byte PTEs
985	movl	a1,a0@(4)		| + segtable address
986	pmove	a0@,srp			| load the supervisor root pointer
987	movl	#0x80000002,a0@		| reinit upper half for CRP loads
988	jra	Lstploaddone		| done
989Lhpmmu2:
990	movl	a1,d1
991	moveq	#PGSHIFT,d2
992	lsrl	d2,d1			| convert to page frame
993	movl	d1,IOBASE+MMUBASE+MMUSSTP | load in sysseg table register
994Lstploaddone:
995	lea	MAXADDR,a2		| PA of last RAM page
996	RELOC(Lhighcode, a1)		| addr of high code
997	RELOC(Lehighcode, a3)		| end addr
998Lcodecopy:
999	movw	a1@+,a2@+		| copy a word
1000	cmpl	a3,a1			| done yet?
1001	jcs	Lcodecopy		| no, keep going
1002	jmp	MAXADDR			| go for it!
1003
1004Lhighcode:
1005	RELOC(_mmutype, a0)
1006	tstl	a0@			| HP MMU?
1007	jeq	Lhpmmu3			| yes, skip
1008	movl	#MMU_IEN+MMU_FPE,IOBASE+MMUBASE+MMUCMD | enable 68881 and i-cache
1009	movl	#0x82c0aa00,a2@			| value to load TC with
1010	pmove	a2@,tc				| load it
1011	jmp	Lenab1
1012Lhpmmu3:
1013	movl	#0,IOBASE+MMUBASE+MMUCMD	| clear external cache
1014	movl	#MMU_ENAB,IOBASE+MMUBASE+MMUCMD	| turn on MMU
1015	jmp	Lenab1				| jmp to mapped code
1016Lehighcode:
1017
1018/*
1019 * Should be running mapped from this point on
1020 */
1021Lenab1:
1022/* check for internal HP-IB in SYSFLAG */
1023	btst	#5,0xfffffed2		| internal HP-IB?
1024	jeq	Linitmem		| yes, have HP-IB just continue
1025	clrl	_internalhpib		| no, clear flag
1026/* init mem sizes */
1027Linitmem:
1028	movl	#MAXADDR,d1		| last page
1029	moveq	#PGSHIFT,d2
1030	lsrl	d2,d1			| convert to page (click) number
1031	movl	d1,_maxmem		| save as maxmem
1032	movl	_lowram,d0		| lowram value from ROM via boot
1033	lsrl	d2,d0			| convert to page number
1034	subl	d0,d1			| compute amount of RAM present
1035	movl	d1,_physmem		| and physmem
1036/*
1037 * pmap_bootstrap is supposed to be called with mapping off early on
1038 * to set up the kernel VA space.  However, this only works easily if
1039 * you have a kernel PA == VA mapping.  Since we do not, we just set
1040 * up and enable mapping here and then call the bootstrap routine to
1041 * get the pmap module in sync with reality.
1042 */
1043	.globl	_avail_start
1044	lea	tmpstk,sp		| temporary stack
1045	movl	a5,sp@-			| phys load address (assumes VA 0)
1046	movl	a4,sp@-			| first available PA
1047	jbsr	_pmap_bootstrap		| sync up pmap module
1048	addql	#8,sp
1049|	movl	_avail_start,a4		| pmap_bootstrap may need RAM
1050/* set kernel stack, user SP, and initial pcb */
1051	lea	_kstack,a1		| proc0 kernel stack
1052	lea	a1@(UPAGES*NBPG-4),sp	| set kernel stack to end of area
1053	movl	#USRSTACK-4,a2
1054	movl	a2,usp			| init user SP
1055	movl	_proc0paddr,a1		| get proc0 pcb addr
1056	movl	a1,_masterpaddr		| proc0 is running
1057	clrw	a1@(PCB_FLAGS)		| clear flags
1058#ifdef FPCOPROC
1059	clrl	a1@(PCB_FPCTX)		| ensure null FP context
1060	movl	a1,sp@-
1061	jbsr	_m68881_restore		| restore it (does not kill a1)
1062	addql	#4,sp
1063#endif
1064/* flush TLB and turn on caches */
1065	jbsr	_TBIA			| invalidate TLB
1066	movl	#CACHE_ON,d0
1067	movc	d0,cacr			| clear cache(s)
1068	tstl	_ectype
1069	jeq	Lnocache0
1070	MMUADDR(a0)
1071	orl	#MMU_CEN,a0@(MMUCMD)	| turn on external cache
1072Lnocache0:
1073/* final setup for C code */
1074	movw	#PSL_LOWIPL,sr		| lower SPL
1075	movl	d7,_boothowto		| save reboot flags
1076	movl	d6,_bootdev		|   and boot device
1077	movl	a4,d1			| addr of first available RAM
1078	moveq	#PGSHIFT,d2
1079	lsrl	d2,d1			| convert to click
1080	movl	d1,sp@-			| param to main
1081	jbsr	_main			| main(firstaddr)
1082	addql	#4,sp
1083/* proc[1] == init now running here;
1084 * create a null exception frame and return to user mode in icode
1085 */
1086	clrw	sp@-			| vector offset/frame type
1087	clrl	sp@-			| return to icode location 0
1088	movw	#PSL_USER,sp@-		| in user mode
1089	rte
1090
1091/*
1092 * Signal "trampoline" code (18 bytes).  Invoked from RTE setup by sendsig().
1093 *
1094 * Stack looks like:
1095 *
1096 *	sp+0 ->	signal number
1097 *	sp+4	signal specific code
1098 *	sp+8	pointer to signal context frame (scp)
1099 *	sp+12	address of handler
1100 *	sp+16	saved hardware state
1101 *			.
1102 *			.
1103 *	scp+0->	beginning of signal context frame
1104 */
1105	.globl	_sigcode, _esigcode
1106	.data
1107_sigcode:
1108	movl	sp@(12),a0		| signal handler addr	(4 bytes)
1109	jsr	a0@			| call signal handler	(2 bytes)
1110	addql	#4,sp			| pop signo		(2 bytes)
1111	trap	#1			| special syscall entry	(2 bytes)
1112	movl	d0,sp@(4)		| save errno		(4 bytes)
1113	moveq	#1,d0			| syscall == exit	(2 bytes)
1114	trap	#0			| exit(errno)		(2 bytes)
1115_esigcode:
1116
1117/*
1118 * Icode is copied out to process 1 to exec init.
1119 * If the exec fails, process 1 exits.
1120 */
1121	.globl	_icode,_szicode
1122	.text
1123_icode:
1124	clrl	sp@-
1125	pea	pc@((argv-.)+2)
1126	pea	pc@((init-.)+2)
1127	clrl	sp@-
1128	moveq	#SYS_execve,d0
1129	trap	#0
1130	moveq	#SYS_exit,d0
1131	trap	#0
1132init:
1133	.asciz	"/sbin/init"
1134	.even
1135argv:
1136	.long	init+6-_icode		| argv[0] = "init" ("/sbin/init" + 6)
1137	.long	eicode-_icode		| argv[1] follows icode after copyout
1138	.long	0
1139eicode:
1140
1141_szicode:
1142	.long	_szicode-_icode
1143
1144/*
1145 * Primitives
1146 */
1147
1148#ifdef GPROF
1149#ifdef __GNUC__
1150#define	ENTRY(name) \
1151	.globl _/**/name; _/**/name: link a6,#0; jbsr mcount; unlk a6
1152#define ALTENTRY(name, rname) \
1153	ENTRY(name); jra rname+12
1154#else
1155#define	ENTRY(name) \
1156	.globl _/**/name; _/**/name: jbsr mcount
1157#define ALTENTRY(name, rname) \
1158	ENTRY(name); jra rname+6
1159#endif
1160#else
1161#define	ENTRY(name) \
1162	.globl _/**/name; _/**/name:
1163#define ALTENTRY(name, rname) \
1164	.globl _/**/name; _/**/name:
1165#endif
1166
1167/*
1168 * update profiling information for the user
1169 * addupc(pc, &u.u_prof, ticks)
1170 */
1171ENTRY(addupc)
1172	movl	a2,sp@-			| scratch register
1173	movl	sp@(12),a2		| get &u.u_prof
1174	movl	sp@(8),d0		| get user pc
1175	subl	a2@(8),d0		| pc -= pr->pr_off
1176	jlt	Lauexit			| less than 0, skip it
1177	movl	a2@(12),d1		| get pr->pr_scale
1178	lsrl	#1,d0			| pc /= 2
1179	lsrl	#1,d1			| scale /= 2
1180	mulul	d1,d0			| pc /= scale
1181	moveq	#14,d1
1182	lsrl	d1,d0			| pc >>= 14
1183	bclr	#0,d0			| pc &= ~1
1184	cmpl	a2@(4),d0		| too big for buffer?
1185	jge	Lauexit			| yes, screw it
1186	addl	a2@,d0			| no, add base
1187	movl	d0,sp@-			| push address
1188	jbsr	_fusword		| grab old value
1189	movl	sp@+,a0			| grab address back
1190	cmpl	#-1,d0			| access ok
1191	jeq	Lauerror		| no, skip out
1192	addw	sp@(18),d0		| add tick to current value
1193	movl	d0,sp@-			| push value
1194	movl	a0,sp@-			| push address
1195	jbsr	_susword		| write back new value
1196	addql	#8,sp			| pop params
1197	tstl	d0			| fault?
1198	jeq	Lauexit			| no, all done
1199Lauerror:
1200	clrl	a2@(12)			| clear scale (turn off prof)
1201Lauexit:
1202	movl	sp@+,a2			| restore scratch reg
1203	rts
1204
1205/*
1206 * copyinstr(fromaddr, toaddr, maxlength, &lencopied)
1207 *
1208 * Copy a null terminated string from the user address space into
1209 * the kernel address space.
1210 * NOTE: maxlength must be < 64K
1211 */
1212ENTRY(copyinstr)
1213	movl	_masterpaddr,a0		| current pcb
1214	movl	#Lcisflt1,a0@(PCB_ONFAULT) | set up to catch faults
1215	movl	sp@(4),a0		| a0 = fromaddr
1216	movl	sp@(8),a1		| a1 = toaddr
1217	moveq	#0,d0
1218	movw	sp@(14),d0		| d0 = maxlength
1219	jlt	Lcisflt1		| negative count, error
1220	jeq	Lcisdone		| zero count, all done
1221	subql	#1,d0			| set up for dbeq
1222Lcisloop:
1223	movsb	a0@+,d1			| grab a byte
1224	movb	d1,a1@+			| copy it
1225	dbeq	d0,Lcisloop		| if !null and more, continue
1226	jne	Lcisflt2		| ran out of room, error
1227	moveq	#0,d0			| got a null, all done
1228Lcisdone:
1229	tstl	sp@(16)			| return length desired?
1230	jeq	Lcisret			| no, just return
1231	subl	sp@(4),a0		| determine how much was copied
1232	movl	sp@(16),a1		| return location
1233	movl	a0,a1@			| stash it
1234Lcisret:
1235	movl	_masterpaddr,a0		| current pcb
1236	clrl	a0@(PCB_ONFAULT) 	| clear fault addr
1237	rts
1238Lcisflt1:
1239	moveq	#EFAULT,d0		| copy fault
1240	jra	Lcisdone
1241Lcisflt2:
1242	moveq	#ENAMETOOLONG,d0	| ran out of space
1243	jra	Lcisdone
1244
1245/*
1246 * copyoutstr(fromaddr, toaddr, maxlength, &lencopied)
1247 *
1248 * Copy a null terminated string from the kernel
1249 * address space to the user address space.
1250 * NOTE: maxlength must be < 64K
1251 */
1252ENTRY(copyoutstr)
1253	movl	_masterpaddr,a0		| current pcb
1254	movl	#Lcosflt1,a0@(PCB_ONFAULT) | set up to catch faults
1255	movl	sp@(4),a0		| a0 = fromaddr
1256	movl	sp@(8),a1		| a1 = toaddr
1257	moveq	#0,d0
1258	movw	sp@(14),d0		| d0 = maxlength
1259	jlt	Lcosflt1		| negative count, error
1260	jeq	Lcosdone		| zero count, all done
1261	subql	#1,d0			| set up for dbeq
1262Lcosloop:
1263	movb	a0@+,d1			| grab a byte
1264	movsb	d1,a1@+			| copy it
1265	dbeq	d0,Lcosloop		| if !null and more, continue
1266	jne	Lcosflt2		| ran out of room, error
1267	moveq	#0,d0			| got a null, all done
1268Lcosdone:
1269	tstl	sp@(16)			| return length desired?
1270	jeq	Lcosret			| no, just return
1271	subl	sp@(4),a0		| determine how much was copied
1272	movl	sp@(16),a1		| return location
1273	movl	a0,a1@			| stash it
1274Lcosret:
1275	movl	_masterpaddr,a0		| current pcb
1276	clrl	a0@(PCB_ONFAULT) 	| clear fault addr
1277	rts
1278Lcosflt1:
1279	moveq	#EFAULT,d0		| copy fault
1280	jra	Lcosdone
1281Lcosflt2:
1282	moveq	#ENAMETOOLONG,d0	| ran out of space
1283	jra	Lcosdone
1284
1285/*
1286 * copystr(fromaddr, toaddr, maxlength, &lencopied)
1287 *
1288 * Copy a null terminated string from one point to another in
1289 * the kernel address space.
1290 * NOTE: maxlength must be < 64K
1291 */
1292ENTRY(copystr)
1293	movl	_masterpaddr,a0		| current pcb
1294	movl	#Lcsflt1,a0@(PCB_ONFAULT) | set up to catch faults
1295	movl	sp@(4),a0		| a0 = fromaddr
1296	movl	sp@(8),a1		| a1 = toaddr
1297	moveq	#0,d0
1298	movw	sp@(14),d0		| d0 = maxlength
1299	jlt	Lcsflt1			| negative count, error
1300	jeq	Lcsdone			| zero count, all done
1301	subql	#1,d0			| set up for dbeq
1302Lcsloop:
1303	movb	a0@+,a1@+		| copy a byte
1304	dbeq	d0,Lcsloop		| if !null and more, continue
1305	jne	Lcsflt2			| ran out of room, error
1306	moveq	#0,d0			| got a null, all done
1307Lcsdone:
1308	tstl	sp@(16)			| return length desired?
1309	jeq	Lcsret			| no, just return
1310	subl	sp@(4),a0		| determine how much was copied
1311	movl	sp@(16),a1		| return location
1312	movl	a0,a1@			| stash it
1313Lcsret:
1314	movl	_masterpaddr,a0		| current pcb
1315	clrl	a0@(PCB_ONFAULT) 	| clear fault addr
1316	rts
1317Lcsflt1:
1318	moveq	#EFAULT,d0		| copy fault
1319	jra	Lcsdone
1320Lcsflt2:
1321	moveq	#ENAMETOOLONG,d0	| ran out of space
1322	jra	Lcsdone
1323
1324/*
1325 * Copyin(from, to, len)
1326 *
1327 * Copy specified amount of data from user space into the kernel.
1328 * NOTE: len must be < 64K
1329 */
1330ENTRY(copyin)
1331	movl	d2,sp@-			| scratch register
1332	movl	_masterpaddr,a0		| current pcb
1333	movl	#Lciflt,a0@(PCB_ONFAULT) | set up to catch faults
1334	movl	sp@(16),d2		| check count
1335	jlt	Lciflt			| negative, error
1336	jeq	Lcidone			| zero, done
1337	movl	sp@(8),a0		| src address
1338	movl	sp@(12),a1		| dest address
1339	movl	a0,d0
1340	btst	#0,d0			| src address odd?
1341	jeq	Lcieven			| no, go check dest
1342	movsb	a0@+,d1			| yes, get a byte
1343	movb	d1,a1@+			| put a byte
1344	subql	#1,d2			| adjust count
1345	jeq	Lcidone			| exit if done
1346Lcieven:
1347	movl	a1,d0
1348	btst	#0,d0			| dest address odd?
1349	jne	Lcibyte			| yes, must copy by bytes
1350	movl	d2,d0			| no, get count
1351	lsrl	#2,d0			| convert to longwords
1352	jeq	Lcibyte			| no longwords, copy bytes
1353	subql	#1,d0			| set up for dbf
1354Lcilloop:
1355	movsl	a0@+,d1			| get a long
1356	movl	d1,a1@+			| put a long
1357	dbf	d0,Lcilloop		| til done
1358	andl	#3,d2			| what remains
1359	jeq	Lcidone			| all done
1360Lcibyte:
1361	subql	#1,d2			| set up for dbf
1362Lcibloop:
1363	movsb	a0@+,d1			| get a byte
1364	movb	d1,a1@+			| put a byte
1365	dbf	d2,Lcibloop		| til done
1366Lcidone:
1367	moveq	#0,d0			| success
1368Lciexit:
1369	movl	_masterpaddr,a0		| current pcb
1370	clrl	a0@(PCB_ONFAULT) 	| clear fault catcher
1371	movl	sp@+,d2			| restore scratch reg
1372	rts
1373Lciflt:
1374	moveq	#EFAULT,d0		| got a fault
1375	jra	Lciexit
1376
1377/*
1378 * Copyout(from, to, len)
1379 *
1380 * Copy specified amount of data from kernel to the user space
1381 * NOTE: len must be < 64K
1382 */
1383ENTRY(copyout)
1384	movl	d2,sp@-			| scratch register
1385	movl	_masterpaddr,a0		| current pcb
1386	movl	#Lcoflt,a0@(PCB_ONFAULT) | catch faults
1387	movl	sp@(16),d2		| check count
1388	jlt	Lcoflt			| negative, error
1389	jeq	Lcodone			| zero, done
1390	movl	sp@(8),a0		| src address
1391	movl	sp@(12),a1		| dest address
1392	movl	a0,d0
1393	btst	#0,d0			| src address odd?
1394	jeq	Lcoeven			| no, go check dest
1395	movb	a0@+,d1			| yes, get a byte
1396	movsb	d1,a1@+			| put a byte
1397	subql	#1,d2			| adjust count
1398	jeq	Lcodone			| exit if done
1399Lcoeven:
1400	movl	a1,d0
1401	btst	#0,d0			| dest address odd?
1402	jne	Lcobyte			| yes, must copy by bytes
1403	movl	d2,d0			| no, get count
1404	lsrl	#2,d0			| convert to longwords
1405	jeq	Lcobyte			| no longwords, copy bytes
1406	subql	#1,d0			| set up for dbf
1407Lcolloop:
1408	movl	a0@+,d1			| get a long
1409	movsl	d1,a1@+			| put a long
1410	dbf	d0,Lcolloop		| til done
1411	andl	#3,d2			| what remains
1412	jeq	Lcodone			| all done
1413Lcobyte:
1414	subql	#1,d2			| set up for dbf
1415Lcobloop:
1416	movb	a0@+,d1			| get a byte
1417	movsb	d1,a1@+			| put a byte
1418	dbf	d2,Lcobloop		| til done
1419Lcodone:
1420	moveq	#0,d0			| success
1421Lcoexit:
1422	movl	_masterpaddr,a0		| current pcb
1423	clrl	a0@(PCB_ONFAULT) 	| clear fault catcher
1424	movl	sp@+,d2			| restore scratch reg
1425	rts
1426Lcoflt:
1427	moveq	#EFAULT,d0		| got a fault
1428	jra	Lcoexit
1429
1430/*
1431 * non-local gotos
1432 */
1433ENTRY(setjmp)
1434	movl	sp@(4),a0	| savearea pointer
1435	moveml	#0xFCFC,a0@	| save d2-d7/a2-a7
1436	movl	sp@,a0@(48)	| and return address
1437	moveq	#0,d0		| return 0
1438	rts
1439
1440ENTRY(qsetjmp)
1441	movl	sp@(4),a0	| savearea pointer
1442	lea	a0@(40),a0	| skip regs we do not save
1443	movl	a6,a0@+		| save FP
1444	movl	sp,a0@+		| save SP
1445	movl	sp@,a0@		| and return address
1446	moveq	#0,d0		| return 0
1447	rts
1448
1449ENTRY(longjmp)
1450	movl	sp@(4),a0
1451	moveml	a0@+,#0xFCFC
1452	movl	a0@,sp@
1453	moveq	#1,d0
1454	rts
1455
1456/*
1457 * The following primitives manipulate the run queues.
1458 * _whichqs tells which of the 32 queues _qs
1459 * have processes in them.  Setrq puts processes into queues, Remrq
1460 * removes them from queues.  The running process is on no queue,
1461 * other processes are on a queue related to p->p_pri, divided by 4
1462 * actually to shrink the 0-127 range of priorities into the 32 available
1463 * queues.
1464 */
1465
1466	.globl	_whichqs,_qs,_cnt,_panic
1467	.globl	_curproc
1468	.comm	_want_resched,4
1469
1470/*
1471 * Setrq(p)
1472 *
1473 * Call should be made at spl6(), and p->p_stat should be SRUN
1474 */
1475ENTRY(setrq)
1476	movl	sp@(4),a0
1477	tstl	a0@(P_RLINK)
1478	jeq	Lset1
1479	movl	#Lset2,sp@-
1480	jbsr	_panic
1481Lset1:
1482	clrl	d0
1483	movb	a0@(P_PRI),d0
1484	lsrb	#2,d0
1485	movl	_whichqs,d1
1486	bset	d0,d1
1487	movl	d1,_whichqs
1488	lslb	#3,d0
1489	addl	#_qs,d0
1490	movl	d0,a0@(P_LINK)
1491	movl	d0,a1
1492	movl	a1@(P_RLINK),a0@(P_RLINK)
1493	movl	a0,a1@(P_RLINK)
1494	movl	a0@(P_RLINK),a1
1495	movl	a0,a1@(P_LINK)
1496	rts
1497
1498Lset2:
1499	.asciz	"setrq"
1500	.even
1501
1502/*
1503 * Remrq(p)
1504 *
1505 * Call should be made at spl6().
1506 */
1507ENTRY(remrq)
1508	movl	sp@(4),a0
1509	clrl	d0
1510	movb	a0@(P_PRI),d0
1511	lsrb	#2,d0
1512	movl	_whichqs,d1
1513	bclr	d0,d1
1514	jne	Lrem1
1515	movl	#Lrem3,sp@-
1516	jbsr	_panic
1517Lrem1:
1518	movl	d1,_whichqs
1519	movl	a0@(P_LINK),a1
1520	movl	a0@(P_RLINK),a1@(P_RLINK)
1521	movl	a0@(P_RLINK),a1
1522	movl	a0@(P_LINK),a1@(P_LINK)
1523	movl	#_qs,a1
1524	movl	d0,d1
1525	lslb	#3,d1
1526	addl	d1,a1
1527	cmpl	a1@(P_LINK),a1
1528	jeq	Lrem2
1529	movl	_whichqs,d1
1530	bset	d0,d1
1531	movl	d1,_whichqs
1532Lrem2:
1533	clrl	a0@(P_RLINK)
1534	rts
1535
1536Lrem3:
1537	.asciz	"remrq"
1538Lsw0:
1539	.asciz	"swtch"
1540	.even
1541
1542/*
1543 * Masterpaddr is the p->p_addr of the running process on the master
1544 * processor.  When a multiprocessor system, the slave processors will have
1545 * an array of slavepaddrs (on an HP it only exists for the benefit of adb).
1546 */
1547	.globl	_masterpaddr
1548	.data
1549_masterpaddr:
1550	.long	0
1551pcbflag:
1552	.byte	0		| copy of pcb_flags low byte
1553	.align	2
1554	.comm	_nullpcb,SIZEOF_PCB
1555	.text
1556
1557/*
1558 * At exit of a process, do a swtch for the last time.
1559 */
1560ENTRY(swtch_exit)
1561	movl	#_nullpcb,_masterpaddr
1562	lea	tmpstk,sp		| goto a tmp stack
1563	jra	_swtch
1564
1565/*
1566 * When no processes are on the runq, Swtch branches to idle
1567 * to wait for something to come ready.
1568 */
1569	.globl	Idle
1570Idle:
1571idle:
1572	movw	#PSL_LOWIPL,sr
1573	tstl	_whichqs
1574	jne	Lsw1
1575	stop	#PSL_LOWIPL
1576	jra	idle
1577
1578Lbadsw:
1579	movl	#Lsw0,sp@-
1580	jbsr	_panic
1581	/*NOTREACHED*/
1582
1583/*
1584 * Swtch()
1585 */
1586ENTRY(swtch)
1587	movl	_masterpaddr,a0		| current pcb
1588	movw	sr,a0@(PCB_PS)		| save sr before changing ipl
1589#ifdef notyet
1590	movl	_curproc,sp@-		| remember last proc running
1591#endif
1592	clrl	_curproc
1593	addql	#1,_cnt+V_SWTCH
1594Lsw1:
1595	/*
1596	 * Find the highest-priority queue that isn't empty,
1597	 * then take the first proc from that queue.
1598	 */
1599	clrl	d0
1600	movl	_whichqs,d1
1601Lswchk:
1602	btst	d0,d1
1603	jne	Lswfnd
1604	addqb	#1,d0
1605	cmpb	#32,d0
1606	jne	Lswchk
1607	jra	idle
1608Lswfnd:
1609	movw	#PSL_HIGHIPL,sr
1610	movl	_whichqs,d1
1611	bclr	d0,d1
1612	jeq	Lsw1
1613	movl	d1,_whichqs
1614	movl	d0,d1
1615	lslb	#3,d1
1616	addl	#_qs,d1
1617	movl	d1,a1
1618	cmpl	a1@(P_LINK),a1
1619	jeq	Lbadsw
1620	movl	a1@(P_LINK),a0		| a0 is selected proc
1621	movl	a0@(P_LINK),a1@(P_LINK)
1622	movl	a0@(P_LINK),a1
1623	movl	a0@(P_RLINK),a1@(P_RLINK)
1624	cmpl	a0@(P_LINK),d1
1625	jeq	Lsw2
1626	movl	_whichqs,d1
1627	bset	d0,d1
1628	movl	d1,_whichqs
1629Lsw2:
1630	movl	a0,_curproc
1631	clrl	_want_resched
1632#ifdef notyet
1633	movl	sp@+,a1
1634	cmpl	a0,a1			| switching to same proc?
1635	jeq	Lswdone			| yes, skip save and restore
1636#endif
1637	/*
1638	 * Save state of previous process in its pcb.
1639	 */
1640	movl	_masterpaddr,a1
1641	movl	usp,a0			| grab USP
1642	movl	a0,a1@(PCB_USP)		| and save it
1643	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1644	movl	_CMAP2,a1@(PCB_CMAP2)	| save temporary map PTE
1645#ifdef FPCOPROC
1646	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1647	fsave	a0@			| save FP state
1648	tstb	a0@			| null state frame?
1649	jeq	Lswnofpsave		| yes, all done
1650	fmovem	fp0-fp7,a0@(216)	| save FP general registers
1651	fmovem	fpcr/fpsr/fpi,a0@(312)	| save FP control registers
1652Lswnofpsave:
1653#endif
1654
1655	movl	_curproc,a0
1656#ifdef DIAGNOSTIC
1657	tstl	a0@(P_WCHAN)
1658	jne	Lbadsw
1659	cmpb	#SRUN,a0@(P_STAT)
1660	jne	Lbadsw
1661#endif
1662	clrl	a0@(P_RLINK)
1663	movl	a0@(P_ADDR),a1
1664	movl	a1,_masterpaddr
1665	movb	a1@(PCB_FLAGS+1),pcbflag | copy of pcb_flags low byte
1666	movl	a0@(P_VMSPACE),a0	| map = p->p_vmspace
1667	tstl	a0			| map == VM_MAP_NULL? ???
1668	jeq	Lswnochg		| yes, skip
1669	movl	a0@(PMAP),a0		| pmap = map->pmap
1670	tstl	a0			| pmap == PMAP_NULL? ???
1671	jeq	Lswnochg		| yes, skip
1672	tstl	a0@(PM_STCHG)		| pmap->st_changed?
1673	jeq	Lswnochg		| no, skip
1674	pea	a1@			| push pcb (at p_addr)
1675	pea	a0@			| push pmap
1676	jbsr	_pmap_activate		| pmap_activate(pmap, pcb)
1677	addql	#8,sp
1678	movl    _masterpaddr,a1         | restore p_addr
1679Lswnochg:
1680
1681/*
1682 * NOTE: on the PMMU we attempt to avoid flushing the entire TAC.
1683 * The effort involved in selective flushing may not be worth it,
1684 * maybe we should just flush the whole thing?
1685 */
1686#ifdef PROFTIMER
1687	movw	#SPL6,sr		| protect against clock interrupts
1688	bclr	#0,_profon		| clear user profiling bit, was set?
1689	jeq	Lskipoff		| no, clock off or doing kernel only
1690#ifdef GPROF
1691	tstb	_profon			| kernel profiling also enabled?
1692	jlt	Lskipoff		| yes, nothing more to do
1693#endif
1694	CLKADDR(a0)
1695	movb	#0,a0@(CLKCR2)		| no, just user, select CR3
1696	movb	#0,a0@(CLKCR3)		| and turn it off
1697Lskipoff:
1698#endif
1699	movl	#PGSHIFT,d1
1700	movl	a1,d0
1701	lsrl	d1,d0			| convert p_addr to page number
1702	lsll	#2,d0			| and now to Systab offset
1703	addl	_Sysmap,d0		| add Systab base to get PTE addr
1704	movw	#PSL_HIGHIPL,sr		| go crit while changing PTEs
1705	lea	tmpstk,sp		| now goto a tmp stack for NMI
1706	movl	d0,a0			| address of new context
1707	movl	_Umap,a1		| address of PTEs for kstack
1708	moveq	#UPAGES-1,d0		| sizeof kstack
1709Lres1:
1710	movl	a0@+,d1			| get PTE
1711	andl	#~PG_PROT,d1		| mask out old protection
1712	orl	#PG_RW+PG_V,d1		| ensure valid and writable
1713	movl	d1,a1@+			| load it up
1714	dbf	d0,Lres1		| til done
1715	movl	_masterpaddr,a1		| reload pcb pointer
1716	movl	#CACHE_CLR,d0
1717	movc	d0,cacr			| invalidate cache(s)
1718#if defined(HP330) || defined(HP360) || defined(HP370)
1719	tstl	_mmutype		| HP MMU?
1720	jeq	Lhpmmu4			| yes, skip
1721	jmi	Lnot68851a		| must flush all on 68030 MMU
1722#ifdef DEBUG
1723	tstl	fulltflush		| 68851, conservative?
1724	jne	Lnot68851a		| yes, go flush all
1725#endif
1726	pflushs	#4,#4			| flush only supervisor side
1727	jra	Lres2
1728Lnot68851a:
1729	pflusha				| flush entire TLB
1730Lres2:
1731	movl	a1@(PCB_USTP),d0	| get USTP
1732	moveq	#PGSHIFT,d1
1733	lsll	d1,d0			| convert to addr
1734	lea	_protorp,a0		| CRP prototype
1735	movl	d0,a0@(4)		| stash USTP
1736	pmove	a0@,crp			| load new user root pointer
1737	jra	Lcxswdone		| thats it
1738Lhpmmu4:
1739#endif
1740#if defined(HP320) || defined(HP350)
1741	MMUADDR(a0)
1742	movl	a0@(MMUTBINVAL),d1	| invalidate TLB
1743	tstl	_ectype			| got external VAC?
1744	jle	Lnocache1		| no, skip
1745	andl	#~MMU_CEN,a0@(MMUCMD)	| toggle cache enable
1746	orl	#MMU_CEN,a0@(MMUCMD)	| to clear data cache
1747Lnocache1:
1748	movl	a1@(PCB_USTP),a0@(MMUUSTP) | context switch
1749#endif
1750Lcxswdone:
1751#if defined(HP330)
1752	jeq	Lnot68851b		| if set need to flush user TLB
1753	tstl	_mmutype		| 68851 PMMU?
1754	jle	Lnot68851b		| no, skip
1755	pflushs	#0,#4			| user PT changed, flush user TLB
1756Lnot68851b:
1757#endif
1758	movl	a1@(PCB_CMAP2),_CMAP2	| reload tmp map
1759	moveml	a1@(PCB_REGS),#0xFCFC	| and registers
1760	movl	a1@(PCB_USP),a0
1761	movl	a0,usp			| and USP
1762#ifdef PROFTIMER
1763	tstl	a1@(U_PROFSCALE)	| process being profiled?
1764	jeq	Lskipon			| no, do nothing
1765	orb	#1,_profon		| turn on user profiling bit
1766#ifdef GPROF
1767	jlt	Lskipon			| already profiling kernel, all done
1768#endif
1769	CLKADDR(a0)
1770	movl	_profint,d1		| profiling interval
1771	subql	#1,d1			|   adjusted
1772	movepw	d1,a0@(CLKMSB3)		| set interval
1773	movb	#0,a0@(CLKCR2)		| select CR3
1774	movb	#64,a0@(CLKCR3)		| turn it on
1775Lskipon:
1776#endif
1777#ifdef FPCOPROC
1778	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1779	tstb	a0@			| null state frame?
1780	jeq	Lresfprest		| yes, easy
1781	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
1782	fmovem	a0@(216),fp0-fp7	| restore FP general registers
1783Lresfprest:
1784	frestore a0@			| restore state
1785#endif
1786	tstl	a1@(PCB_SSWAP)		| do an alternate return?
1787	jne	Lres3			| yes, do non-local goto
1788	movw	a1@(PCB_PS),sr		| no, restore PS
1789	rts
1790
1791	/*
1792	 * simulate longjmp returning from savectx;
1793	 * that frame wasn't active when this stack was copied,
1794	 * although savectx's caller's stack was active,
1795	 * and savectx will have saved sp while it was active.
1796	 * Construct fake frame from which to "return".
1797	 */
1798Lres3:
1799	movl	a1@(PCB_SSWAP),sp@	| alternate return pc; fake call frame
1800	clrl	a1@(PCB_SSWAP)		| clear flag
1801	movw	a1@(PCB_PS),sr		| restore PS
1802	moveq	#1,d0			| return 1
1803	rts
1804
1805/*
1806 * savectx(pcb, altreturn)
1807 * Update pcb, saving current processor state and arranging
1808 * for alternate return ala longjmp in swtch if altreturn is true.
1809 */
1810ENTRY(savectx)
1811	movl	sp@(4),a1
1812	movw	sr,a1@(PCB_PS)
1813	movl	usp,a0			| grab USP
1814	movl	a0,a1@(PCB_USP)		| and save it
1815	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1816	movl	_CMAP2,a1@(PCB_CMAP2)	| save temporary map PTE
1817#ifdef FPCOPROC
1818	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1819	fsave	a0@			| save FP state
1820	tstb	a0@			| null state frame?
1821	jeq	Lsvnofpsave		| yes, all done
1822	fmovem	fp0-fp7,a0@(216)	| save FP general registers
1823	fmovem	fpcr/fpsr/fpi,a0@(312)	| save FP control registers
1824Lsvnofpsave:
1825#endif
1826	tstl	sp@(8)			| altreturn?
1827	jeq	Lsavedone
1828	movl	sp@,a1@(PCB_SSWAP)	| alternate return address
1829Lsavedone:
1830	moveq	#0,d0			| return 0
1831	rts
1832
1833/*
1834 * {fu,su},{byte,sword,word}
1835 */
1836ALTENTRY(fuiword, _fuword)
1837ENTRY(fuword)
1838	movl	sp@(4),d0		| address to read
1839	btst	#0,d0			| is it odd?
1840	jne	Lfserr			| yes, a fault
1841	movl	_masterpaddr,a0		| current pcb
1842	movl	#Lfserr,a0@(PCB_ONFAULT) | where to return to on a fault
1843	movl	d0,a0
1844	movsl	a0@,d0			| do read from user space
1845	jra	Lfsdone
1846
1847ENTRY(fusword)
1848	movl	sp@(4),d0
1849	btst	#0,d0			| is address odd?
1850	jne	Lfserr			| yes, a fault
1851	movl	_masterpaddr,a0		| current pcb
1852	movl	#Lfserr,a0@(PCB_ONFAULT) | where to return to on a fault
1853	movl	d0,a0			| address to read
1854	moveq	#0,d0
1855	movsw	a0@,d0			| do read from user space
1856	jra	Lfsdone
1857
1858ALTENTRY(fuibyte, _fubyte)
1859ENTRY(fubyte)
1860	movl	_masterpaddr,a0		| current pcb
1861	movl	#Lfserr,a0@(PCB_ONFAULT) | where to return to on a fault
1862	movl	sp@(4),a0		| address to read
1863	moveq	#0,d0
1864	movsb	a0@,d0			| do read from user space
1865	jra	Lfsdone
1866
1867Lfserr:
1868	moveq	#-1,d0			| error indicator
1869Lfsdone:
1870	movl	_masterpaddr,a0		| current pcb
1871	clrl	a0@(PCB_ONFAULT) 	| clear fault address
1872	rts
1873
1874ALTENTRY(suiword, _suword)
1875ENTRY(suword)
1876	movl	sp@(4),d0		| address to write
1877	btst	#0,d0			| is it odd?
1878	jne	Lfserr			| yes, a fault
1879	movl	_masterpaddr,a0		| current pcb
1880	movl	#Lfserr,a0@(PCB_ONFAULT) | where to return to on a fault
1881	movl	d0,a0			| address to write
1882	movl	sp@(8),d0		| value to put there
1883	movsl	d0,a0@			| do write to user space
1884	moveq	#0,d0			| indicate no fault
1885	jra	Lfsdone
1886
1887ENTRY(susword)
1888	movl	sp@(4),d0		| address to write
1889	btst	#0,d0			| is it odd?
1890	jne	Lfserr			| yes, a fault
1891	movl	_masterpaddr,a0		| current pcb
1892	movl	#Lfserr,a0@(PCB_ONFAULT) | where to return to on a fault
1893	movl	d0,a0			| address to write
1894	movw	sp@(10),d0		| value to put there
1895	movsw	d0,a0@			| do write to user space
1896	moveq	#0,d0			| indicate no fault
1897	jra	Lfsdone
1898
1899ALTENTRY(suibyte, _subyte)
1900ENTRY(subyte)
1901	movl	_masterpaddr,a0		| current pcb
1902	movl	#Lfserr,a0@(PCB_ONFAULT) | where to return to on a fault
1903	movl	sp@(4),a0		| address to write
1904	movb	sp@(11),d0		| value to put there
1905	movsb	d0,a0@			| do write to user space
1906	moveq	#0,d0			| indicate no fault
1907	jra	Lfsdone
1908
1909/*
1910 * Copy 1 relocation unit (NBPG bytes)
1911 * from user virtual address to physical address
1912 */
1913ENTRY(copyseg)
1914	movl	_masterpaddr,a0			| current pcb
1915	movl	#Lcpydone,a0@(PCB_ONFAULT)	| where to return to on a fault
1916	movl	sp@(8),d0			| destination page number
1917	moveq	#PGSHIFT,d1
1918	lsll	d1,d0				| convert to address
1919	orl	#PG_CI+PG_RW+PG_V,d0		| make sure valid and writable
1920	movl	_CMAP2,a0
1921	movl	_CADDR2,sp@-			| destination kernel VA
1922	movl	d0,a0@				| load in page table
1923	jbsr	_TBIS				| invalidate any old mapping
1924	addql	#4,sp
1925	movl	_CADDR2,a1			| destination addr
1926	movl	sp@(4),a0			| source addr
1927	movl	#NBPG/4-1,d0			| count
1928Lcpyloop:
1929	movsl	a0@+,d1				| read longword
1930	movl	d1,a1@+				| write longword
1931	dbf	d0,Lcpyloop			| continue until done
1932Lcpydone:
1933	movl	_masterpaddr,a0			| current pcb
1934	clrl	a0@(PCB_ONFAULT) 		| clear error catch
1935	rts
1936
1937/*
1938 * Copy 1 relocation unit (NBPG bytes)
1939 * from physical address to physical address
1940 */
1941ENTRY(physcopyseg)
1942	movl	sp@(4),d0			| source page number
1943	moveq	#PGSHIFT,d1
1944	lsll	d1,d0				| convert to address
1945	orl	#PG_CI+PG_RW+PG_V,d0		| make sure valid and writable
1946	movl	_CMAP1,a0
1947	movl	d0,a0@				| load in page table
1948	movl	_CADDR1,sp@-			| destination kernel VA
1949	jbsr	_TBIS				| invalidate any old mapping
1950	addql	#4,sp
1951
1952	movl	sp@(8),d0			| destination page number
1953	moveq	#PGSHIFT,d1
1954	lsll	d1,d0				| convert to address
1955	orl	#PG_CI+PG_RW+PG_V,d0		| make sure valid and writable
1956	movl	_CMAP2,a0
1957	movl	d0,a0@				| load in page table
1958	movl	_CADDR2,sp@-			| destination kernel VA
1959	jbsr	_TBIS				| invalidate any old mapping
1960	addql	#4,sp
1961
1962	movl	_CADDR1,a0			| source addr
1963	movl	_CADDR2,a1			| destination addr
1964	movl	#NBPG/4-1,d0			| count
1965Lpcpy:
1966	movl	a0@+,a1@+			| copy longword
1967	dbf	d0,Lpcpy			| continue until done
1968	rts
1969
1970/*
1971 * zero out physical memory
1972 * specified in relocation units (NBPG bytes)
1973 */
1974ENTRY(clearseg)
1975	movl	sp@(4),d0			| destination page number
1976	moveq	#PGSHIFT,d1
1977	lsll	d1,d0				| convert to address
1978	orl	#PG_CI+PG_RW+PG_V,d0		| make sure valid and writable
1979	movl	_CMAP1,a0
1980	movl	_CADDR1,sp@-			| destination kernel VA
1981	movl	d0,a0@				| load in page map
1982	jbsr	_TBIS				| invalidate any old mapping
1983	addql	#4,sp
1984	movl	_CADDR1,a1			| destination addr
1985	movl	#NBPG/4-1,d0			| count
1986/* simple clear loop is fastest on 68020 */
1987Lclrloop:
1988	clrl	a1@+				| clear a longword
1989	dbf	d0,Lclrloop			| continue til done
1990	rts
1991
1992/*
1993 * Invalidate entire TLB.
1994 */
1995ENTRY(TBIA)
1996__TBIA:
1997#if defined(HP330) || defined(HP360) || defined(HP370)
1998	tstl	_mmutype		| HP MMU?
1999	jeq	Lhpmmu6			| yes, skip
2000	pflusha				| flush entire TLB
2001#if defined(HP360) || defined(HP370)
2002	jpl	Lmc68851a		| 68851 implies no d-cache
2003	movl	#DC_CLEAR,d0
2004	movc	d0,cacr			| invalidate on-chip d-cache
2005Lmc68851a:
2006#endif
2007	rts
2008Lhpmmu6:
2009#endif
2010#if defined(HP320) || defined(HP350)
2011	MMUADDR(a0)
2012	movl	a0@(MMUTBINVAL),sp@-	| do not ask me, this
2013	addql	#4,sp			|   is how hpux does it
2014#ifdef DEBUG
2015	tstl	fullcflush
2016	jne	__DCIA			| XXX: invalidate entire cache
2017#endif
2018#endif
2019	rts
2020
2021/*
2022 * Invalidate any TLB entry for given VA (TB Invalidate Single)
2023 */
2024ENTRY(TBIS)
2025#ifdef DEBUG
2026	tstl	fulltflush		| being conservative?
2027	jne	__TBIA			| yes, flush entire TLB
2028#endif
2029#if defined(HP330) || defined(HP360) || defined(HP370)
2030	tstl	_mmutype		| HP MMU?
2031	jeq	Lhpmmu5			| yes, skip
2032	movl	sp@(4),a0		| get addr to flush
2033#if defined(HP360) || defined(HP370)
2034	jpl	Lmc68851b		| is 68851?
2035	pflush	#0,#0,a0@		| flush address from both sides
2036	movl	#DC_CLEAR,d0
2037	movc	d0,cacr			| invalidate on-chip data cache
2038	rts
2039Lmc68851b:
2040#endif
2041	pflushs	#0,#0,a0@		| flush address from both sides
2042	rts
2043Lhpmmu5:
2044#endif
2045#if defined(HP320) || defined(HP350)
2046	movl	sp@(4),d0		| VA to invalidate
2047	bclr	#0,d0			| ensure even
2048	movl	d0,a0
2049	movw	sr,d1			| go critical
2050	movw	#PSL_HIGHIPL,sr		|   while in purge space
2051	moveq	#FC_PURGE,d0		| change address space
2052	movc	d0,dfc			|   for destination
2053	moveq	#0,d0			| zero to invalidate?
2054	movsl	d0,a0@			| hit it
2055	moveq	#FC_USERD,d0		| back to old
2056	movc	d0,dfc			|   address space
2057	movw	d1,sr			| restore IPL
2058#endif
2059	rts
2060
2061/*
2062 * Invalidate supervisor side of TLB
2063 */
2064ENTRY(TBIAS)
2065#ifdef DEBUG
2066	tstl	fulltflush		| being conservative?
2067	jne	__TBIA			| yes, flush everything
2068#endif
2069#if defined(HP330) || defined(HP360) || defined(HP370)
2070	tstl	_mmutype		| HP MMU?
2071	jeq	Lhpmmu7			| yes, skip
2072#if defined(HP360) || defined(HP370)
2073	jpl	Lmc68851c		| 68851?
2074	pflush #4,#4			| flush supervisor TLB entries
2075	movl	#DC_CLEAR,d0
2076	movc	d0,cacr			| invalidate on-chip d-cache
2077	rts
2078Lmc68851c:
2079#endif
2080	pflushs #4,#4			| flush supervisor TLB entries
2081	rts
2082Lhpmmu7:
2083#endif
2084#if defined(HP320) || defined(HP350)
2085	MMUADDR(a0)
2086	movl	#0x8000,d0		| more
2087	movl	d0,a0@(MMUTBINVAL)	|   HP magic
2088#ifdef DEBUG
2089	tstl	fullcflush
2090	jne	__DCIS			| XXX: invalidate entire sup. cache
2091#endif
2092#endif
2093	rts
2094
2095/*
2096 * Invalidate user side of TLB
2097 */
2098ENTRY(TBIAU)
2099#ifdef DEBUG
2100	tstl	fulltflush		| being conservative?
2101	jne	__TBIA			| yes, flush everything
2102#endif
2103#if defined(HP330) || defined(HP360) || defined(HP370)
2104	tstl	_mmutype		| HP MMU?
2105	jeq	Lhpmmu8			| yes, skip
2106#if defined(HP360) || defined(HP370)
2107	jpl	Lmc68851d		| 68851?
2108	pflush	#0,#4			| flush user TLB entries
2109	movl	#DC_CLEAR,d0
2110	movc	d0,cacr			| invalidate on-chip d-cache
2111	rts
2112Lmc68851d:
2113#endif
2114	pflushs	#0,#4			| flush user TLB entries
2115	rts
2116Lhpmmu8:
2117#endif
2118#if defined(HP320) || defined(HP350)
2119	MMUADDR(a0)
2120	moveq	#0,d0			| more
2121	movl	d0,a0@(MMUTBINVAL)	|   HP magic
2122#ifdef DEBUG
2123	tstl	fullcflush
2124	jne	__DCIU			| XXX: invalidate entire user cache
2125#endif
2126#endif
2127	rts
2128
2129/*
2130 * Invalidate instruction cache
2131 */
2132ENTRY(ICIA)
2133	movl	#IC_CLEAR,d0
2134	movc	d0,cacr			| invalidate i-cache
2135	rts
2136
2137/*
2138 * Invalidate data cache.
2139 * HP external cache allows for invalidation of user/supervisor portions.
2140 * NOTE: we do not flush 68030 on-chip cache as there are no aliasing
2141 * problems with DC_WA.  The only cases we have to worry about are context
2142 * switch and TLB changes, both of which are handled "in-line" in resume
2143 * and TBI*.
2144 */
2145ENTRY(DCIA)
2146__DCIA:
2147#if defined(HP320) || defined(HP350)
2148	tstl	_ectype			| got external VAC?
2149	jle	Lnocache2		| no, all done
2150	MMUADDR(a0)
2151	andl	#~MMU_CEN,a0@(MMUCMD)	| disable cache in MMU control reg
2152	orl	#MMU_CEN,a0@(MMUCMD)	| reenable cache in MMU control reg
2153Lnocache2:
2154#endif
2155	rts
2156
2157ENTRY(DCIS)
2158__DCIS:
2159#if defined(HP320) || defined(HP350)
2160	tstl	_ectype			| got external VAC?
2161	jle	Lnocache3		| no, all done
2162	MMUADDR(a0)
2163	movl	a0@(MMUSSTP),d0		| read the supervisor STP
2164	movl	d0,a0@(MMUSSTP)		| write it back
2165Lnocache3:
2166#endif
2167	rts
2168
2169ENTRY(DCIU)
2170__DCIU:
2171#if defined(HP320) || defined(HP350)
2172	tstl	_ectype			| got external VAC?
2173	jle	Lnocache4		| no, all done
2174	MMUADDR(a0)
2175	movl	a0@(MMUUSTP),d0		| read the user STP
2176	movl	d0,a0@(MMUUSTP)		| write it back
2177Lnocache4:
2178#endif
2179	rts
2180
2181ENTRY(PCIA)
2182#if defined(HP360) || defined(HP370)
2183	movl	#DC_CLEAR,d0
2184	movc	d0,cacr			| invalidate on-chip d-cache
2185	tstl	_ectype			| got external PAC?
2186	jge	Lnocache6		| no, all done
2187	MMUADDR(a0)
2188	andl	#~MMU_CEN,a0@(MMUCMD)	| disable cache in MMU control reg
2189	orl	#MMU_CEN,a0@(MMUCMD)	| reenable cache in MMU control reg
2190Lnocache6:
2191#endif
2192	rts
2193
2194ENTRY(ecacheon)
2195	tstl	_ectype
2196	jeq	Lnocache7
2197	MMUADDR(a0)
2198	orl	#MMU_CEN,a0@(MMUCMD)
2199Lnocache7:
2200	rts
2201
2202ENTRY(ecacheoff)
2203	tstl	_ectype
2204	jeq	Lnocache8
2205	MMUADDR(a0)
2206	andl	#~MMU_CEN,a0@(MMUCMD)
2207Lnocache8:
2208	rts
2209
2210	.globl	_getsfc, _getdfc
2211_getsfc:
2212	movc	sfc,d0
2213	rts
2214_getdfc:
2215	movc	dfc,d0
2216	rts
2217
2218/*
2219 * Load a new user segment table pointer.
2220 */
2221ENTRY(loadustp)
2222#if defined(HP330) || defined(HP360) || defined(HP370)
2223	tstl	_mmutype		| HP MMU?
2224	jeq	Lhpmmu9			| yes, skip
2225	movl	sp@(4),d0		| new USTP
2226	moveq	#PGSHIFT,d1
2227	lsll	d1,d0			| convert to addr
2228	lea	_protorp,a0		| CRP prototype
2229	movl	d0,a0@(4)		| stash USTP
2230	pmove	a0@,crp			| load root pointer
2231	movl	#DC_CLEAR,d0
2232	movc	d0,cacr			| invalidate on-chip d-cache
2233	rts				|   since pmove flushes TLB
2234Lhpmmu9:
2235#endif
2236#if defined(HP320) || defined(HP350)
2237	MMUADDR(a0)
2238	movl	sp@(4),a0@(MMUUSTP)	| load a new USTP
2239#endif
2240	rts
2241
2242/*
2243 * Flush any hardware context associated with given USTP.
2244 * Only does something for HP330 where we must flush RPT
2245 * and ATC entries in PMMU.
2246 */
2247ENTRY(flushustp)
2248#if defined(HP330)
2249	tstl	_mmutype		| 68851 PMMU?
2250	jle	Lnot68851		| no, nothing to do
2251	movl	sp@(4),d0		| get USTP to flush
2252	moveq	#PGSHIFT,d1
2253	lsll	d1,d0			| convert to address
2254	movl	d0,_protorp+4		| stash USTP
2255	pflushr	_protorp		| flush RPT/TLB entries
2256Lnot68851:
2257#endif
2258	rts
2259
2260ENTRY(ploadw)
2261#if defined(HP330) || defined(HP360) || defined(HP370)
2262	movl	sp@(4),a0		| address to load
2263	ploadw	#1,a0@			| pre-load translation
2264#endif
2265	rts
2266
2267/*
2268 * Set processor priority level calls.  Most could (should) be replaced
2269 * by inline asm expansions.  However, SPL0 and SPLX require special
2270 * handling.  If we are returning to the base processor priority (SPL0)
2271 * we need to check for our emulated software interrupts.
2272 */
2273
2274ENTRY(spl0)
2275	moveq	#0,d0
2276	movw	sr,d0			| get old SR for return
2277	movw	#PSL_LOWIPL,sr		| restore new SR
2278	jra	Lsplsir
2279
2280ENTRY(splx)
2281	moveq	#0,d0
2282	movw	sr,d0			| get current SR for return
2283	movw	sp@(6),d1		| get new value
2284	movw	d1,sr			| restore new SR
2285	andw	#PSL_IPL7,d1		| mask all but PSL_IPL
2286	jne	Lspldone		| non-zero, all done
2287Lsplsir:
2288	tstb	_ssir			| software interrupt pending?
2289	jeq	Lspldone		| no, all done
2290	subql	#4,sp			| make room for RTE frame
2291	movl	sp@(4),sp@(2)		| position return address
2292	clrw	sp@(6)			| set frame type 0
2293	movw	#PSL_LOWIPL,sp@		| and new SR
2294	jra	Lgotsir			| go handle it
2295Lspldone:
2296	rts
2297
2298ALTENTRY(splsoftclock, _spl1)
2299ALTENTRY(splnet, _spl1)
2300ENTRY(spl1)
2301	moveq	#0,d0
2302	movw	sr,d0
2303	movw	#SPL1,sr
2304	rts
2305
2306ENTRY(spl2)
2307	moveq	#0,d0
2308	movw	sr,d0
2309	movw	#SPL2,sr
2310	rts
2311
2312ENTRY(spl3)
2313	moveq	#0,d0
2314	movw	sr,d0
2315	movw	#SPL3,sr
2316	rts
2317
2318ENTRY(spl4)
2319	moveq	#0,d0
2320	movw	sr,d0
2321	movw	#SPL4,sr
2322	rts
2323
2324ALTENTRY(splimp, _spl5)
2325ALTENTRY(splbio, _spl5)
2326ALTENTRY(spltty, _spl5)
2327ENTRY(spl5)
2328	moveq	#0,d0
2329	movw	sr,d0
2330	movw	#SPL5,sr
2331	rts
2332
2333ALTENTRY(splclock, _spl6)
2334ENTRY(spl6)
2335	moveq	#0,d0
2336	movw	sr,d0
2337	movw	#SPL6,sr
2338	rts
2339
2340ALTENTRY(splhigh, _spl7)
2341ENTRY(spl7)
2342	moveq	#0,d0
2343	movw	sr,d0
2344	movw	#PSL_HIGHIPL,sr
2345	rts
2346
2347#ifdef GPROF
2348/*
2349 * Special versions of splhigh and splx called by mcount().
2350 * Note that __splx does not check for software interrupts.
2351 */
2352	.globl	__splhigh, __splx
2353__splhigh:
2354	moveq	#0,d0
2355	movw	sr,d0
2356	movw	#PSL_HIGHIPL,sr
2357	rts
2358
2359__splx:
2360	moveq	#0,d0
2361	movw	sr,d0			| get current SR for return
2362	movw	sp@(6),d1		| get new value
2363	movw	d1,sr			| restore new SR
2364	rts
2365#endif
2366
2367ENTRY(_insque)
2368	movw	sr,d0
2369	movw	#PSL_HIGHIPL,sr		| atomic
2370	movl	sp@(8),a0		| where to insert (after)
2371	movl	sp@(4),a1		| element to insert (e)
2372	movl	a0@,a1@			| e->next = after->next
2373	movl	a0,a1@(4)		| e->prev = after
2374	movl	a1,a0@			| after->next = e
2375	movl	a1@,a0
2376	movl	a1,a0@(4)		| e->next->prev = e
2377	movw	d0,sr
2378	rts
2379
2380ENTRY(_remque)
2381	movw	sr,d0
2382	movw	#PSL_HIGHIPL,sr		| atomic
2383	movl	sp@(4),a0		| element to remove (e)
2384	movl	a0@,a1
2385	movl	a0@(4),a0
2386	movl	a0,a1@(4)		| e->next->prev = e->prev
2387	movl	a1,a0@			| e->prev->next = e->next
2388	movw	d0,sr
2389	rts
2390
2391/*
2392 * bzero(addr, count)
2393 */
2394ALTENTRY(blkclr, _bzero)
2395ENTRY(bzero)
2396	movl	sp@(4),a0	| address
2397	movl	sp@(8),d0	| count
2398	jeq	Lbzdone		| if zero, nothing to do
2399	movl	a0,d1
2400	btst	#0,d1		| address odd?
2401	jeq	Lbzeven		| no, can copy words
2402	clrb	a0@+		| yes, zero byte to get to even boundary
2403	subql	#1,d0		| decrement count
2404	jeq	Lbzdone		| none left, all done
2405Lbzeven:
2406	movl	d0,d1
2407	andl	#31,d0
2408	lsrl	#5,d1		| convert count to 8*longword count
2409	jeq	Lbzbyte		| no such blocks, zero byte at a time
2410Lbzloop:
2411	clrl	a0@+; clrl	a0@+; clrl	a0@+; clrl	a0@+;
2412	clrl	a0@+; clrl	a0@+; clrl	a0@+; clrl	a0@+;
2413	subql	#1,d1		| one more block zeroed
2414	jne	Lbzloop		| more to go, do it
2415	tstl	d0		| partial block left?
2416	jeq	Lbzdone		| no, all done
2417Lbzbyte:
2418	clrb	a0@+
2419	subql	#1,d0		| one more byte cleared
2420	jne	Lbzbyte		| more to go, do it
2421Lbzdone:
2422	rts
2423
2424/*
2425 * strlen(str)
2426 */
2427ENTRY(strlen)
2428	moveq	#-1,d0
2429	movl	sp@(4),a0	| string
2430Lslloop:
2431	addql	#1,d0		| increment count
2432	tstb	a0@+		| null?
2433	jne	Lslloop		| no, keep going
2434	rts
2435
2436/*
2437 * bcmp(s1, s2, len)
2438 *
2439 * WARNING!  This guy only works with counts up to 64K
2440 */
2441ENTRY(bcmp)
2442	movl	sp@(4),a0		| string 1
2443	movl	sp@(8),a1		| string 2
2444	moveq	#0,d0
2445	movw	sp@(14),d0		| length
2446	jeq	Lcmpdone		| if zero, nothing to do
2447	subqw	#1,d0			| set up for DBcc loop
2448Lcmploop:
2449	cmpmb	a0@+,a1@+		| equal?
2450	dbne	d0,Lcmploop		| yes, keep going
2451	addqw	#1,d0			| +1 gives zero on match
2452Lcmpdone:
2453	rts
2454
2455/*
2456 * {ov}bcopy(from, to, len)
2457 *
2458 * Works for counts up to 128K.
2459 */
2460ALTENTRY(ovbcopy, _bcopy)
2461ENTRY(bcopy)
2462	movl	sp@(12),d0		| get count
2463	jeq	Lcpyexit		| if zero, return
2464	movl	sp@(4),a0		| src address
2465	movl	sp@(8),a1		| dest address
2466	cmpl	a1,a0			| src before dest?
2467	jlt	Lcpyback		| yes, copy backwards (avoids overlap)
2468	movl	a0,d1
2469	btst	#0,d1			| src address odd?
2470	jeq	Lcfeven			| no, go check dest
2471	movb	a0@+,a1@+		| yes, copy a byte
2472	subql	#1,d0			| update count
2473	jeq	Lcpyexit		| exit if done
2474Lcfeven:
2475	movl	a1,d1
2476	btst	#0,d1			| dest address odd?
2477	jne	Lcfbyte			| yes, must copy by bytes
2478	movl	d0,d1			| no, get count
2479	lsrl	#2,d1			| convert to longwords
2480	jeq	Lcfbyte			| no longwords, copy bytes
2481	subql	#1,d1			| set up for dbf
2482Lcflloop:
2483	movl	a0@+,a1@+		| copy longwords
2484	dbf	d1,Lcflloop		| til done
2485	andl	#3,d0			| get remaining count
2486	jeq	Lcpyexit		| done if none
2487Lcfbyte:
2488	subql	#1,d0			| set up for dbf
2489Lcfbloop:
2490	movb	a0@+,a1@+		| copy bytes
2491	dbf	d0,Lcfbloop		| til done
2492Lcpyexit:
2493	rts
2494Lcpyback:
2495	addl	d0,a0			| add count to src
2496	addl	d0,a1			| add count to dest
2497	movl	a0,d1
2498	btst	#0,d1			| src address odd?
2499	jeq	Lcbeven			| no, go check dest
2500	movb	a0@-,a1@-		| yes, copy a byte
2501	subql	#1,d0			| update count
2502	jeq	Lcpyexit		| exit if done
2503Lcbeven:
2504	movl	a1,d1
2505	btst	#0,d1			| dest address odd?
2506	jne	Lcbbyte			| yes, must copy by bytes
2507	movl	d0,d1			| no, get count
2508	lsrl	#2,d1			| convert to longwords
2509	jeq	Lcbbyte			| no longwords, copy bytes
2510	subql	#1,d1			| set up for dbf
2511Lcblloop:
2512	movl	a0@-,a1@-		| copy longwords
2513	dbf	d1,Lcblloop		| til done
2514	andl	#3,d0			| get remaining count
2515	jeq	Lcpyexit		| done if none
2516Lcbbyte:
2517	subql	#1,d0			| set up for dbf
2518Lcbbloop:
2519	movb	a0@-,a1@-		| copy bytes
2520	dbf	d0,Lcbbloop		| til done
2521	rts
2522
2523/*
2524 * Emulate fancy VAX string operations:
2525 *	scanc(count, startc, table, mask)
2526 *	skpc(mask, count, startc)
2527 *	locc(mask, count, startc)
2528 */
2529ENTRY(scanc)
2530	movl	sp@(4),d0	| get length
2531	jeq	Lscdone		| nothing to do, return
2532	movl	sp@(8),a0	| start of scan
2533	movl	sp@(12),a1	| table to compare with
2534	movb	sp@(19),d1	| and mask to use
2535	movw	d2,sp@-		| need a scratch register
2536	clrw	d2		| clear it out
2537	subqw	#1,d0		| adjust for dbra
2538Lscloop:
2539	movb	a0@+,d2		| get character
2540	movb	a1@(0,d2:w),d2	| get table entry
2541	andb	d1,d2		| mask it
2542	dbne	d0,Lscloop	| keep going til no more or non-zero
2543	addqw	#1,d0		| overshot by one
2544	movw	sp@+,d2		| restore scratch
2545Lscdone:
2546	rts
2547
2548ENTRY(skpc)
2549	movl	sp@(8),d0	| get length
2550	jeq	Lskdone		| nothing to do, return
2551	movb	sp@(7),d1	| mask to use
2552	movl	sp@(12),a0	| where to start
2553	subqw	#1,d0		| adjust for dbcc
2554Lskloop:
2555	cmpb	a0@+,d1		| compate with mask
2556	dbne	d0,Lskloop	| keep going til no more or zero
2557	addqw	#1,d0		| overshot by one
2558Lskdone:
2559	rts
2560
2561ENTRY(locc)
2562	movl	sp@(8),d0	| get length
2563	jeq	Llcdone		| nothing to do, return
2564	movb	sp@(7),d1	| mask to use
2565	movl	sp@(12),a0	| where to start
2566	subqw	#1,d0		| adjust for dbcc
2567Llcloop:
2568	cmpb	a0@+,d1		| compate with mask
2569	dbeq	d0,Llcloop	| keep going til no more or non-zero
2570	addqw	#1,d0		| overshot by one
2571Llcdone:
2572	rts
2573
2574/*
2575 * Emulate VAX FFS (find first set) instruction.
2576 */
2577ENTRY(ffs)
2578	moveq	#-1,d0
2579	movl	sp@(4),d1
2580	jeq	Lffsdone
2581Lffsloop:
2582	addql	#1,d0
2583	btst	d0,d1
2584	jeq	Lffsloop
2585Lffsdone:
2586	addql	#1,d0
2587	rts
2588
2589#ifdef FPCOPROC
2590/*
2591 * Save and restore 68881 state.
2592 * Pretty awful looking since our assembler does not
2593 * recognize FP mnemonics.
2594 */
2595ENTRY(m68881_save)
2596	movl	sp@(4),a0		| save area pointer
2597	fsave	a0@			| save state
2598	tstb	a0@			| null state frame?
2599	jeq	Lm68881sdone		| yes, all done
2600	fmovem fp0-fp7,a0@(216)		| save FP general registers
2601	fmovem fpcr/fpsr/fpi,a0@(312)	| save FP control registers
2602Lm68881sdone:
2603	rts
2604
2605ENTRY(m68881_restore)
2606	movl	sp@(4),a0		| save area pointer
2607	tstb	a0@			| null state frame?
2608	jeq	Lm68881rdone		| yes, easy
2609	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
2610	fmovem	a0@(216),fp0-fp7	| restore FP general registers
2611Lm68881rdone:
2612	frestore a0@			| restore state
2613	rts
2614#endif
2615
2616/*
2617 * Handle the nitty-gritty of rebooting the machine.
2618 * Basically we just turn off the MMU and jump to the appropriate ROM routine.
2619 * Note that we must be running in an address range that is mapped one-to-one
2620 * logical to physical so that the PC is still valid immediately after the MMU
2621 * is turned off.  We have conveniently mapped the last page of physical
2622 * memory this way.
2623 */
2624	.globl	_doboot
2625_doboot:
2626	movl	#CACHE_OFF,d0
2627	movc	d0,cacr			| disable on-chip cache(s)
2628#if defined(HP320) || defined(HP350) || defined(HP370)
2629	tstl	_ectype
2630	jeq	Lnocache5
2631	MMUADDR(a0)
2632	andl	#~MMU_CEN,a0@(MMUCMD)	| disable external cache
2633Lnocache5:
2634#endif
2635	lea	MAXADDR,a0		| last page of physical memory
2636	movl	_boothowto,a0@+		| store howto
2637	movl	_bootdev,a0@+		| and devtype
2638	lea	Lbootcode,a1		| start of boot code
2639	lea	Lebootcode,a3		| end of boot code
2640Lbootcopy:
2641	movw	a1@+,a0@+		| copy a word
2642	cmpl	a3,a1			| done yet?
2643	jcs	Lbootcopy		| no, keep going
2644	jmp	MAXADDR+8		| jump to last page
2645
2646Lbootcode:
2647	lea	MAXADDR+0x800,sp	| physical SP in case of NMI
2648#if defined(HP330) || defined(HP360) || defined(HP370)
2649	tstl	_mmutype		| HP MMU?
2650	jeq	LhpmmuB			| yes, skip
2651	movl	#0,a0@			| value for pmove to TC (turn off MMU)
2652	pmove	a0@,tc			| disable MMU
2653	jmp	0x1A4			| goto REQ_REBOOT
2654LhpmmuB:
2655#endif
2656#if defined(HP320) || defined(HP350)
2657	MMUADDR(a0)
2658	movl	#0xFFFF0000,a0@(MMUCMD)	| totally disable MMU
2659	movl	d2,MAXADDR+NBPG-4	| restore old high page contents
2660	jmp	0x1A4			| goto REQ_REBOOT
2661#endif
2662Lebootcode:
2663
2664	.data
2665	.space	NBPG
2666tmpstk:
2667	.globl	_machineid
2668_machineid:
2669	.long	0		| default to 320
2670	.globl	_mmutype,_protorp
2671_mmutype:
2672	.long	0		| default to HP MMU
2673_protorp:
2674	.long	0,0		| prototype root pointer
2675	.globl	_ectype
2676_ectype:
2677	.long	0		| external cache type, default to none
2678	.globl	_internalhpib
2679_internalhpib:
2680	.long	1		| has internal HP-IB, default to yes
2681	.globl	_cold
2682_cold:
2683	.long	1		| cold start flag
2684	.globl	_DIObase, _CLKbase, _MMUbase, _proc0paddr
2685_proc0paddr:
2686	.long	0		| KVA of proc0 u-area
2687_DIObase:
2688	.long	0		| KVA of base of IO space
2689_CLKbase:
2690	.long	0		| KVA of base of clock registers
2691_MMUbase:
2692	.long	0		| KVA of base of HP MMU registers
2693#ifdef DEBUG
2694	.globl	fulltflush, fullcflush
2695fulltflush:
2696	.long	0
2697fullcflush:
2698	.long	0
2699	.globl	timebomb
2700timebomb:
2701	.long	0
2702#endif
2703/* interrupt counters */
2704	.globl	_intrcnt,_eintrcnt,_intrnames,_eintrnames
2705_intrnames:
2706	.asciz	"spur"
2707	.asciz	"hil"
2708	.asciz	"lev2"
2709	.asciz	"lev3"
2710	.asciz	"lev4"
2711	.asciz	"lev5"
2712	.asciz	"dma"
2713	.asciz	"clock"
2714#ifdef PROFTIMER
2715	.asciz  "pclock"
2716#endif
2717	.asciz	"nmi"
2718_eintrnames:
2719	.even
2720_intrcnt:
2721#ifdef PROFTIMER
2722	.long	0,0,0,0,0,0,0,0,0,0
2723#else
2724	.long	0,0,0,0,0,0,0,0,0
2725#endif
2726_eintrcnt:
2727