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