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