xref: /original-bsd/sys/hp300/hp300/locore.s (revision 4a884f8b)
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.66 92/12/22$
13 *
14 *	@(#)locore.s	7.22 (Berkeley) 02/18/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 swtch_exit'ed,
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	jbsr	_main			| call main()
1086
1087/* proc[1] == init now running here;
1088 * create a null exception frame and return to user mode in icode
1089 */
1090	cmpl	#-2,_mmutype		| 68040?
1091	jne	Lnoflush		| no, skip
1092	.word	0xf478			| cpusha dc
1093	.word	0xf498			| cinva ic
1094Lnoflush:
1095	clrw	sp@-			| vector offset/frame type
1096	clrl	sp@-			| return to icode location 0
1097	movw	#PSL_USER,sp@-		| in user mode
1098	rte
1099
1100/*
1101 * Signal "trampoline" code (18 bytes).  Invoked from RTE setup by sendsig().
1102 *
1103 * Stack looks like:
1104 *
1105 *	sp+0 ->	signal number
1106 *	sp+4	signal specific code
1107 *	sp+8	pointer to signal context frame (scp)
1108 *	sp+12	address of handler
1109 *	sp+16	saved hardware state
1110 *			.
1111 *			.
1112 *	scp+0->	beginning of signal context frame
1113 */
1114	.globl	_sigcode, _esigcode, _sigcodetrap
1115	.data
1116_sigcode:
1117	movl	sp@(12),a0		| signal handler addr	(4 bytes)
1118	jsr	a0@			| call signal handler	(2 bytes)
1119	addql	#4,sp			| pop signo		(2 bytes)
1120_sigcodetrap:
1121	trap	#1			| special syscall entry	(2 bytes)
1122	movl	d0,sp@(4)		| save errno		(4 bytes)
1123	moveq	#1,d0			| syscall == exit	(2 bytes)
1124	trap	#0			| exit(errno)		(2 bytes)
1125	.align	2
1126_esigcode:
1127
1128/*
1129 * Icode is copied out to process 1 to exec init.
1130 * If the exec fails, process 1 exits.
1131 */
1132	.globl	_icode,_szicode
1133	.text
1134_icode:
1135	clrl	sp@-
1136	pea	pc@((argv-.)+2)
1137	pea	pc@((init-.)+2)
1138	clrl	sp@-
1139	moveq	#SYS_execve,d0
1140	trap	#0
1141	moveq	#SYS_exit,d0
1142	trap	#0
1143init:
1144	.asciz	"/sbin/init"
1145	.even
1146argv:
1147	.long	init+6-_icode		| argv[0] = "init" ("/sbin/init" + 6)
1148	.long	eicode-_icode		| argv[1] follows icode after copyout
1149	.long	0
1150eicode:
1151
1152_szicode:
1153	.long	_szicode-_icode
1154
1155/*
1156 * Primitives
1157 */
1158
1159#ifdef GPROF
1160#define	ENTRY(name) \
1161	.globl _/**/name; _/**/name: link a6,#0; jbsr mcount; unlk a6
1162#define ALTENTRY(name, rname) \
1163	ENTRY(name); jra rname+12
1164#else
1165#define	ENTRY(name) \
1166	.globl _/**/name; _/**/name:
1167#define ALTENTRY(name, rname) \
1168	.globl _/**/name; _/**/name:
1169#endif
1170
1171/*
1172 * For gcc2
1173 */
1174ENTRY(__main)
1175	rts
1176
1177/*
1178 * copyinstr(fromaddr, toaddr, maxlength, &lencopied)
1179 *
1180 * Copy a null terminated string from the user address space into
1181 * the kernel address space.
1182 * NOTE: maxlength must be < 64K
1183 */
1184ENTRY(copyinstr)
1185	movl	_curpcb,a0		| current pcb
1186	movl	#Lcisflt1,a0@(PCB_ONFAULT) | set up to catch faults
1187	movl	sp@(4),a0		| a0 = fromaddr
1188	movl	sp@(8),a1		| a1 = toaddr
1189	moveq	#0,d0
1190	movw	sp@(14),d0		| d0 = maxlength
1191	jlt	Lcisflt1		| negative count, error
1192	jeq	Lcisdone		| zero count, all done
1193	subql	#1,d0			| set up for dbeq
1194Lcisloop:
1195	movsb	a0@+,d1			| grab a byte
1196	nop
1197	movb	d1,a1@+			| copy it
1198	dbeq	d0,Lcisloop		| if !null and more, continue
1199	jne	Lcisflt2		| ran out of room, error
1200	moveq	#0,d0			| got a null, all done
1201Lcisdone:
1202	tstl	sp@(16)			| return length desired?
1203	jeq	Lcisret			| no, just return
1204	subl	sp@(4),a0		| determine how much was copied
1205	movl	sp@(16),a1		| return location
1206	movl	a0,a1@			| stash it
1207Lcisret:
1208	movl	_curpcb,a0		| current pcb
1209	clrl	a0@(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	_curpcb,a0		| current pcb
1227	movl	#Lcosflt1,a0@(PCB_ONFAULT) | set up to catch faults
1228	movl	sp@(4),a0		| a0 = fromaddr
1229	movl	sp@(8),a1		| a1 = toaddr
1230	moveq	#0,d0
1231	movw	sp@(14),d0		| d0 = maxlength
1232	jlt	Lcosflt1		| negative count, error
1233	jeq	Lcosdone		| zero count, all done
1234	subql	#1,d0			| set up for dbeq
1235Lcosloop:
1236	movb	a0@+,d1			| grab a byte
1237	movsb	d1,a1@+			| copy it
1238	nop
1239	dbeq	d0,Lcosloop		| if !null and more, continue
1240	jne	Lcosflt2		| ran out of room, error
1241	moveq	#0,d0			| got a null, all done
1242Lcosdone:
1243	tstl	sp@(16)			| return length desired?
1244	jeq	Lcosret			| no, just return
1245	subl	sp@(4),a0		| determine how much was copied
1246	movl	sp@(16),a1		| return location
1247	movl	a0,a1@			| stash it
1248Lcosret:
1249	movl	_curpcb,a0		| current pcb
1250	clrl	a0@(PCB_ONFAULT) 	| clear fault addr
1251	rts
1252Lcosflt1:
1253	moveq	#EFAULT,d0		| copy fault
1254	jra	Lcosdone
1255Lcosflt2:
1256	moveq	#ENAMETOOLONG,d0	| ran out of space
1257	jra	Lcosdone
1258
1259/*
1260 * copystr(fromaddr, toaddr, maxlength, &lencopied)
1261 *
1262 * Copy a null terminated string from one point to another in
1263 * the kernel address space.
1264 * NOTE: maxlength must be < 64K
1265 */
1266ENTRY(copystr)
1267	movl	sp@(4),a0		| a0 = fromaddr
1268	movl	sp@(8),a1		| a1 = toaddr
1269	moveq	#0,d0
1270	movw	sp@(14),d0		| d0 = maxlength
1271	jlt	Lcsflt1			| negative count, error
1272	jeq	Lcsdone			| zero count, all done
1273	subql	#1,d0			| set up for dbeq
1274Lcsloop:
1275	movb	a0@+,a1@+		| copy a byte
1276	dbeq	d0,Lcsloop		| if !null and more, continue
1277	jne	Lcsflt2			| ran out of room, error
1278	moveq	#0,d0			| got a null, all done
1279Lcsdone:
1280	tstl	sp@(16)			| return length desired?
1281	jeq	Lcsret			| no, just return
1282	subl	sp@(4),a0		| determine how much was copied
1283	movl	sp@(16),a1		| return location
1284	movl	a0,a1@			| stash it
1285Lcsret:
1286	rts
1287Lcsflt1:
1288	moveq	#EFAULT,d0		| copy fault
1289	jra	Lcsdone
1290Lcsflt2:
1291	moveq	#ENAMETOOLONG,d0	| ran out of space
1292	jra	Lcsdone
1293
1294/*
1295 * Copyin(from_user, to_kernel, len)
1296 * Copyout(from_kernel, to_user, len)
1297 *
1298 * Copy specified amount of data between kernel and user space.
1299 *
1300 * XXX both use the DBcc instruction which has 16-bit limitation so only
1301 * 64k units can be copied, where "unit" is either a byte or a longword
1302 * depending on alignment.  To be safe, assume it can copy at most
1303 * 64k bytes.  Don't make MAXBSIZE or MAXPHYS larger than 64k without
1304 * fixing this code!
1305 */
1306ENTRY(copyin)
1307	movl	d2,sp@-			| scratch register
1308	movl	_curpcb,a0		| current pcb
1309	movl	#Lciflt,a0@(PCB_ONFAULT) | set up to catch faults
1310	movl	sp@(16),d2		| check count
1311	jlt	Lciflt			| negative, error
1312	jeq	Lcidone			| zero, done
1313	movl	sp@(8),a0		| src address
1314	movl	sp@(12),a1		| dest address
1315	movl	a0,d0
1316	btst	#0,d0			| src address odd?
1317	jeq	Lcieven			| no, go check dest
1318	movsb	a0@+,d1			| yes, get a byte
1319	nop
1320	movb	d1,a1@+			| put a byte
1321	subql	#1,d2			| adjust count
1322	jeq	Lcidone			| exit if done
1323Lcieven:
1324	movl	a1,d0
1325	btst	#0,d0			| dest address odd?
1326	jne	Lcibyte			| yes, must copy by bytes
1327	movl	d2,d0			| no, get count
1328	lsrl	#2,d0			| convert to longwords
1329	jeq	Lcibyte			| no longwords, copy bytes
1330	subql	#1,d0			| set up for dbf
1331Lcilloop:
1332	movsl	a0@+,d1			| get a long
1333	nop
1334	movl	d1,a1@+			| put a long
1335	dbf	d0,Lcilloop		| til done
1336	andl	#3,d2			| what remains
1337	jeq	Lcidone			| all done
1338Lcibyte:
1339	subql	#1,d2			| set up for dbf
1340Lcibloop:
1341	movsb	a0@+,d1			| get a byte
1342	nop
1343	movb	d1,a1@+			| put a byte
1344	dbf	d2,Lcibloop		| til done
1345Lcidone:
1346	moveq	#0,d0			| success
1347Lciexit:
1348	movl	_curpcb,a0		| current pcb
1349	clrl	a0@(PCB_ONFAULT) 	| clear fault catcher
1350	movl	sp@+,d2			| restore scratch reg
1351	rts
1352Lciflt:
1353	moveq	#EFAULT,d0		| got a fault
1354	jra	Lciexit
1355
1356ENTRY(copyout)
1357	movl	d2,sp@-			| scratch register
1358	movl	_curpcb,a0		| current pcb
1359	movl	#Lcoflt,a0@(PCB_ONFAULT) | catch faults
1360	movl	sp@(16),d2		| check count
1361	jlt	Lcoflt			| negative, error
1362	jeq	Lcodone			| zero, done
1363	movl	sp@(8),a0		| src address
1364	movl	sp@(12),a1		| dest address
1365	movl	a0,d0
1366	btst	#0,d0			| src address odd?
1367	jeq	Lcoeven			| no, go check dest
1368	movb	a0@+,d1			| yes, get a byte
1369	movsb	d1,a1@+			| put a byte
1370	nop
1371	subql	#1,d2			| adjust count
1372	jeq	Lcodone			| exit if done
1373Lcoeven:
1374	movl	a1,d0
1375	btst	#0,d0			| dest address odd?
1376	jne	Lcobyte			| yes, must copy by bytes
1377	movl	d2,d0			| no, get count
1378	lsrl	#2,d0			| convert to longwords
1379	jeq	Lcobyte			| no longwords, copy bytes
1380	subql	#1,d0			| set up for dbf
1381Lcolloop:
1382	movl	a0@+,d1			| get a long
1383	movsl	d1,a1@+			| put a long
1384	nop
1385	dbf	d0,Lcolloop		| til done
1386	andl	#3,d2			| what remains
1387	jeq	Lcodone			| all done
1388Lcobyte:
1389	subql	#1,d2			| set up for dbf
1390Lcobloop:
1391	movb	a0@+,d1			| get a byte
1392	movsb	d1,a1@+			| put a byte
1393	nop
1394	dbf	d2,Lcobloop		| til done
1395Lcodone:
1396	moveq	#0,d0			| success
1397Lcoexit:
1398	movl	_curpcb,a0		| current pcb
1399	clrl	a0@(PCB_ONFAULT) 	| clear fault catcher
1400	movl	sp@+,d2			| restore scratch reg
1401	rts
1402Lcoflt:
1403	moveq	#EFAULT,d0		| got a fault
1404	jra	Lcoexit
1405
1406/*
1407 * non-local gotos
1408 */
1409ENTRY(setjmp)
1410	movl	sp@(4),a0	| savearea pointer
1411	moveml	#0xFCFC,a0@	| save d2-d7/a2-a7
1412	movl	sp@,a0@(48)	| and return address
1413	moveq	#0,d0		| return 0
1414	rts
1415
1416ENTRY(longjmp)
1417	movl	sp@(4),a0
1418	moveml	a0@+,#0xFCFC
1419	movl	a0@,sp@
1420	moveq	#1,d0
1421	rts
1422
1423/*
1424 * The following primitives manipulate the run queues.
1425 * _whichqs tells which of the 32 queues _qs
1426 * have processes in them.  Setrq puts processes into queues, Remrq
1427 * removes them from queues.  The running process is on no queue,
1428 * other processes are on a queue related to p->p_pri, divided by 4
1429 * actually to shrink the 0-127 range of priorities into the 32 available
1430 * queues.
1431 */
1432
1433	.globl	_whichqs,_qs,_cnt,_panic
1434	.globl	_curproc,_want_resched
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	.globl	_curpcb
1509	.globl	_masterpaddr	| XXX compatibility (debuggers)
1510	.data
1511_masterpaddr:			| XXX compatibility (debuggers)
1512_curpcb:
1513	.long	0
1514mdpflag:
1515	.byte	0		| copy of proc md_flags low byte
1516	.align	2
1517	.comm	nullpcb,SIZEOF_PCB
1518	.text
1519
1520/*
1521 * At exit of a process, do a swtch for the last time.
1522 * The mapping of the pcb at p->p_addr has already been deleted,
1523 * and the memory for the pcb+stack has been freed.
1524 * The ipl is high enough to prevent the memory from being reallocated.
1525 */
1526ENTRY(swtch_exit)
1527	movl	#nullpcb,_curpcb	| save state into garbage pcb
1528	lea	tmpstk,sp		| goto a tmp stack
1529	jra	_cpu_swtch
1530
1531/*
1532 * When no processes are on the runq, Swtch branches to idle
1533 * to wait for something to come ready.
1534 */
1535	.globl	idle
1536Lidle:
1537	stop	#PSL_LOWIPL
1538idle:
1539	movw	#PSL_HIGHIPL,sr
1540	tstl	_whichqs
1541	jeq	Lidle
1542	movw	#PSL_LOWIPL,sr
1543	jra	Lsw1
1544
1545Lbadsw:
1546	movl	#Lsw0,sp@-
1547	jbsr	_panic
1548	/*NOTREACHED*/
1549
1550/*
1551 * cpu_swtch()
1552 *
1553 * NOTE: On the mc68851 (318/319/330) we attempt to avoid flushing the
1554 * entire ATC.  The effort involved in selective flushing may not be
1555 * worth it, maybe we should just flush the whole thing?
1556 *
1557 * NOTE 2: With the new VM layout we now no longer know if an inactive
1558 * user's PTEs have been changed (formerly denoted by the SPTECHG p_flag
1559 * bit).  For now, we just always flush the full ATC.
1560 */
1561ENTRY(cpu_swtch)
1562	movl	_curpcb,a0		| current pcb
1563	movw	sr,a0@(PCB_PS)		| save sr before changing ipl
1564#ifdef notyet
1565	movl	_curproc,sp@-		| remember last proc running
1566#endif
1567	clrl	_curproc
1568	addql	#1,_cnt+V_SWTCH
1569
1570Lsw1:
1571	/*
1572	 * Find the highest-priority queue that isn't empty,
1573	 * then take the first proc from that queue.
1574	 */
1575	clrl	d0
1576	lea	_whichqs,a0
1577	movl	a0@,d1
1578Lswchk:
1579	btst	d0,d1
1580	jne	Lswfnd
1581	addqb	#1,d0
1582	cmpb	#32,d0
1583	jne	Lswchk
1584	jra	idle
1585Lswfnd:
1586	movw	#PSL_HIGHIPL,sr		| lock out interrupts
1587	movl	a0@,d1			| and check again...
1588	bclr	d0,d1
1589	jeq	Lsw1			| proc moved, rescan
1590	movl	d1,a0@			| update whichqs
1591	moveq	#1,d1			| double check for higher priority
1592	lsll	d0,d1			| process (which may have snuck in
1593	subql	#1,d1			| while we were finding this one)
1594	andl	a0@,d1
1595	jeq	Lswok			| no one got in, continue
1596	movl	a0@,d1
1597	bset	d0,d1			| otherwise put this one back
1598	movl	d1,a0@
1599	jra	Lsw1			| and rescan
1600Lswok:
1601	movl	d0,d1
1602	lslb	#3,d1			| convert queue number to index
1603	addl	#_qs,d1			| locate queue (q)
1604	movl	d1,a1
1605	cmpl	a1@(P_LINK),a1		| anyone on queue?
1606	jeq	Lbadsw			| no, panic
1607	movl	a1@(P_LINK),a0			| p = q->p_link
1608	movl	a0@(P_LINK),a1@(P_LINK)		| q->p_link = p->p_link
1609	movl	a0@(P_LINK),a1			| q = p->p_link
1610	movl	a0@(P_RLINK),a1@(P_RLINK)	| q->p_rlink = p->p_rlink
1611	cmpl	a0@(P_LINK),d1		| anyone left on queue?
1612	jeq	Lsw2			| no, skip
1613	movl	_whichqs,d1
1614	bset	d0,d1			| yes, reset bit
1615	movl	d1,_whichqs
1616Lsw2:
1617	movl	a0,_curproc
1618	clrl	_want_resched
1619#ifdef notyet
1620	movl	sp@+,a1
1621	cmpl	a0,a1			| switching to same proc?
1622	jeq	Lswdone			| yes, skip save and restore
1623#endif
1624	/*
1625	 * Save state of previous process in its pcb.
1626	 */
1627	movl	_curpcb,a1
1628	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1629	movl	usp,a2			| grab USP (a2 has been saved)
1630	movl	a2,a1@(PCB_USP)		| and save it
1631#ifdef FPCOPROC
1632	lea	a1@(PCB_FPCTX),a2	| pointer to FP save area
1633	fsave	a2@			| save FP state
1634	tstb	a2@			| null state frame?
1635	jeq	Lswnofpsave		| yes, all done
1636	fmovem	fp0-fp7,a2@(216)	| save FP general registers
1637	fmovem	fpcr/fpsr/fpi,a2@(312)	| save FP control registers
1638Lswnofpsave:
1639#endif
1640
1641#ifdef DIAGNOSTIC
1642	tstl	a0@(P_WCHAN)
1643	jne	Lbadsw
1644	cmpb	#SRUN,a0@(P_STAT)
1645	jne	Lbadsw
1646#endif
1647	clrl	a0@(P_RLINK)		| clear back link
1648	movb	a0@(P_MDFLAG+3),mdpflag	| low byte of p_md.md_flags
1649	movl	a0@(P_ADDR),a1		| get p_addr
1650	movl	a1,_curpcb
1651
1652	/* see if pmap_activate needs to be called; should remove this */
1653	movl	a0@(P_VMSPACE),a0	| vmspace = p->p_vmspace
1654#ifdef DIAGNOSTIC
1655	tstl	a0			| map == VM_MAP_NULL?
1656	jeq	Lbadsw			| panic
1657#endif
1658	lea	a0@(VM_PMAP),a0		| pmap = &vmspace.vm_pmap
1659	tstl	a0@(PM_STCHG)		| pmap->st_changed?
1660	jeq	Lswnochg		| no, skip
1661	pea	a1@			| push pcb (at p_addr)
1662	pea	a0@			| push pmap
1663	jbsr	_pmap_activate		| pmap_activate(pmap, pcb)
1664	addql	#8,sp
1665	movl	_curpcb,a1		| restore p_addr
1666Lswnochg:
1667
1668	movl	#PGSHIFT,d1
1669	movl	a1,d0
1670	lsrl	d1,d0			| convert p_addr to page number
1671	lsll	#2,d0			| and now to Sysmap offset
1672	addl	_Sysmap,d0		| add Sysmap base to get PTE addr
1673#ifdef notdef
1674	movw	#PSL_HIGHIPL,sr		| go crit while changing PTEs
1675#endif
1676	lea	tmpstk,sp		| now goto a tmp stack for NMI
1677	movl	d0,a0			| address of new context
1678	movl	_Umap,a2		| address of PTEs for kstack
1679	moveq	#UPAGES-1,d0		| sizeof kstack
1680Lres1:
1681	movl	a0@+,d1			| get PTE
1682	andl	#~PG_PROT,d1		| mask out old protection
1683	orl	#PG_RW+PG_V,d1		| ensure valid and writable
1684	movl	d1,a2@+			| load it up
1685	dbf	d0,Lres1		| til done
1686#if defined(HP380)
1687	cmpl	#-2,_mmutype		| 68040?
1688	jne	Lres1a			| no, skip
1689	.word	0xf518			| yes, pflusha
1690	movl	a1@(PCB_USTP),d0	| get USTP
1691	moveq	#PGSHIFT,d1
1692	lsll	d1,d0			| convert to addr
1693	.long	0x4e7b0806		| movc d0,urp
1694	jra	Lcxswdone
1695Lres1a:
1696#endif
1697	movl	#CACHE_CLR,d0
1698	movc	d0,cacr			| invalidate cache(s)
1699#if defined(HP330) || defined(HP360) || defined(HP370)
1700	tstl	_mmutype		| HP MMU?
1701	jeq	Lhpmmu4			| yes, skip
1702	pflusha				| flush entire TLB
1703	movl	a1@(PCB_USTP),d0	| get USTP
1704	moveq	#PGSHIFT,d1
1705	lsll	d1,d0			| convert to addr
1706	lea	_protorp,a0		| CRP prototype
1707	movl	d0,a0@(4)		| stash USTP
1708	pmove	a0@,crp			| load new user root pointer
1709	jra	Lcxswdone		| thats it
1710Lhpmmu4:
1711#endif
1712#if defined(HP320) || defined(HP350)
1713	MMUADDR(a0)
1714	movl	a0@(MMUTBINVAL),d1	| invalidate TLB
1715	tstl	_ectype			| got external VAC?
1716	jle	Lnocache1		| no, skip
1717	andl	#~MMU_CEN,a0@(MMUCMD)	| toggle cache enable
1718	orl	#MMU_CEN,a0@(MMUCMD)	| to clear data cache
1719Lnocache1:
1720	movl	a1@(PCB_USTP),a0@(MMUUSTP) | context switch
1721#endif
1722Lcxswdone:
1723	moveml	a1@(PCB_REGS),#0xFCFC	| and registers
1724	movl	a1@(PCB_USP),a0
1725	movl	a0,usp			| and USP
1726#ifdef FPCOPROC
1727	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1728	tstb	a0@			| null state frame?
1729	jeq	Lresfprest		| yes, easy
1730#if defined(HP380)
1731	cmpl	#-2,_mmutype		| 68040?
1732	jne	Lresnot040		| no, skip
1733	clrl	sp@-			| yes...
1734	frestore sp@+			| ...magic!
1735Lresnot040:
1736#endif
1737	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
1738	fmovem	a0@(216),fp0-fp7	| restore FP general registers
1739Lresfprest:
1740	frestore a0@			| restore state
1741#endif
1742	movw	a1@(PCB_PS),sr		| no, restore PS
1743	moveq	#1,d0			| return 1 (for alternate returns)
1744	rts
1745
1746/*
1747 * savectx(pcb, altreturn)
1748 * Update pcb, saving current processor state and arranging
1749 * for alternate return ala longjmp in swtch if altreturn is true.
1750 */
1751ENTRY(savectx)
1752	movl	sp@(4),a1
1753	movw	sr,a1@(PCB_PS)
1754	movl	usp,a0			| grab USP
1755	movl	a0,a1@(PCB_USP)		| and save it
1756	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1757#ifdef FPCOPROC
1758	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1759	fsave	a0@			| save FP state
1760	tstb	a0@			| null state frame?
1761	jeq	Lsvnofpsave		| yes, all done
1762	fmovem	fp0-fp7,a0@(216)	| save FP general registers
1763	fmovem	fpcr/fpsr/fpi,a0@(312)	| save FP control registers
1764Lsvnofpsave:
1765#endif
1766	tstl	sp@(8)			| altreturn?
1767	jeq	Lsavedone
1768	movl	sp,d0			| relocate current sp relative to a1
1769	subl	#_kstack,d0		|   (sp is relative to kstack):
1770	addl	d0,a1			|   a1 += sp - kstack;
1771	movl	sp@,a1@			| write return pc at (relocated) sp@
1772Lsavedone:
1773	moveq	#0,d0			| return 0
1774	rts
1775
1776/*
1777 * {fu,su},{byte,sword,word}
1778 */
1779ALTENTRY(fuiword, _fuword)
1780ENTRY(fuword)
1781	movl	sp@(4),a0		| address to read
1782	movl	_curpcb,a1		| current pcb
1783	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1784	movsl	a0@,d0			| do read from user space
1785	nop
1786	jra	Lfsdone
1787
1788ENTRY(fusword)
1789	movl	sp@(4),a0
1790	movl	_curpcb,a1		| current pcb
1791	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1792	moveq	#0,d0
1793	movsw	a0@,d0			| do read from user space
1794	nop
1795	jra	Lfsdone
1796
1797/* Just like fusword, but tells trap code not to page in. */
1798ENTRY(fuswintr)
1799	movl	sp@(4),a0
1800	movl	_curpcb,a1
1801	movl	#_fswintr,a1@(PCB_ONFAULT)
1802	moveq	#0,d0
1803	movsw	a0@,d0
1804	nop
1805	jra	Lfsdone
1806
1807ALTENTRY(fuibyte, _fubyte)
1808ENTRY(fubyte)
1809	movl	sp@(4),a0		| address to read
1810	movl	_curpcb,a1		| current pcb
1811	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1812	moveq	#0,d0
1813	movsb	a0@,d0			| do read from user space
1814	nop
1815	jra	Lfsdone
1816
1817Lfserr:
1818	moveq	#-1,d0			| error indicator
1819Lfsdone:
1820	clrl	a1@(PCB_ONFAULT) 	| clear fault address
1821	rts
1822
1823/* Just like Lfserr, but the address is different (& exported). */
1824	.globl	_fswintr
1825_fswintr:
1826	moveq	#-1,d0
1827	jra	Lfsdone
1828
1829
1830/*
1831 * Write a longword in user instruction space.
1832 * Largely the same as suword but with a final i-cache purge on those
1833 * machines with split caches.
1834 */
1835ENTRY(suiword)
1836	movl	sp@(4),a0		| address to write
1837	movl	sp@(8),d0		| value to put there
1838	movl	_curpcb,a1		| current pcb
1839	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1840	movsl	d0,a0@			| do write to user space
1841	nop
1842	moveq	#0,d0			| indicate no fault
1843#if defined(HP380)
1844	cmpl	#-2,_mmutype		| 68040?
1845	jne	Lsuicpurge		| no, skip
1846	.word	0xf498			| cinva ic (XXX overkill)
1847	jra	Lfsdone
1848Lsuicpurge:
1849#endif
1850	movl	#IC_CLEAR,d1
1851	movc	d1,cacr			| invalidate i-cache
1852	jra	Lfsdone
1853
1854ENTRY(suword)
1855	movl	sp@(4),a0		| address to write
1856	movl	sp@(8),d0		| value to put there
1857	movl	_curpcb,a1		| current pcb
1858	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1859	movsl	d0,a0@			| do write to user space
1860	nop
1861	moveq	#0,d0			| indicate no fault
1862	jra	Lfsdone
1863
1864ENTRY(susword)
1865	movl	sp@(4),a0		| address to write
1866	movw	sp@(10),d0		| value to put there
1867	movl	_curpcb,a1		| current pcb
1868	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1869	movsw	d0,a0@			| do write to user space
1870	nop
1871	moveq	#0,d0			| indicate no fault
1872	jra	Lfsdone
1873
1874ENTRY(suswintr)
1875	movl	sp@(4),a0
1876	movw	sp@(10),d0
1877	movl	_curpcb,a1
1878	movl	#_fswintr,a1@(PCB_ONFAULT)
1879	movsw	d0,a0@
1880	nop
1881	moveq	#0,d0
1882	jra	Lfsdone
1883
1884ALTENTRY(suibyte, _subyte)
1885ENTRY(subyte)
1886	movl	sp@(4),a0		| address to write
1887	movb	sp@(11),d0		| value to put there
1888	movl	_curpcb,a1		| current pcb
1889	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1890	movsb	d0,a0@			| do write to user space
1891	nop
1892	moveq	#0,d0			| indicate no fault
1893	jra	Lfsdone
1894
1895#if defined(HP380)
1896ENTRY(suline)
1897	movl	sp@(4),a0		| address to write
1898	movl	_curpcb,a1		| current pcb
1899	movl	#Lslerr,a1@(PCB_ONFAULT) | where to return to on a fault
1900	movl	sp@(8),a1		| address of line
1901	movl	a1@+,d0			| get lword
1902	movsl	d0,a0@+			| put lword
1903	nop				| sync
1904	movl	a1@+,d0			| get lword
1905	movsl	d0,a0@+			| put lword
1906	nop				| sync
1907	movl	a1@+,d0			| get lword
1908	movsl	d0,a0@+			| put lword
1909	nop				| sync
1910	movl	a1@+,d0			| get lword
1911	movsl	d0,a0@+			| put lword
1912	nop				| sync
1913	moveq	#0,d0			| indicate no fault
1914	jra	Lsldone
1915Lslerr:
1916	moveq	#-1,d0
1917Lsldone:
1918	movl	_curpcb,a1		| current pcb
1919	clrl	a1@(PCB_ONFAULT) 	| clear fault address
1920	rts
1921#endif
1922
1923/*
1924 * Invalidate entire TLB.
1925 */
1926ENTRY(TBIA)
1927__TBIA:
1928#if defined(HP380)
1929	cmpl	#-2,_mmutype		| 68040?
1930	jne	Lmotommu3		| no, skip
1931	.word	0xf518			| yes, pflusha
1932	rts
1933Lmotommu3:
1934#endif
1935#if defined(HP330) || defined(HP360) || defined(HP370)
1936	tstl	_mmutype		| HP MMU?
1937	jeq	Lhpmmu6			| yes, skip
1938	pflusha				| flush entire TLB
1939#if defined(HP360) || defined(HP370)
1940	jpl	Lmc68851a		| 68851 implies no d-cache
1941	movl	#DC_CLEAR,d0
1942	movc	d0,cacr			| invalidate on-chip d-cache
1943Lmc68851a:
1944#endif
1945	rts
1946Lhpmmu6:
1947#endif
1948#if defined(HP320) || defined(HP350)
1949	MMUADDR(a0)
1950	movl	a0@(MMUTBINVAL),sp@-	| do not ask me, this
1951	addql	#4,sp			|   is how hpux does it
1952#ifdef DEBUG
1953	tstl	fullcflush
1954	jne	__DCIA			| XXX: invalidate entire cache
1955#endif
1956#endif
1957	rts
1958
1959/*
1960 * Invalidate any TLB entry for given VA (TB Invalidate Single)
1961 */
1962ENTRY(TBIS)
1963#ifdef DEBUG
1964	tstl	fulltflush		| being conservative?
1965	jne	__TBIA			| yes, flush entire TLB
1966#endif
1967#if defined(HP380)
1968	cmpl	#-2,_mmutype		| 68040?
1969	jne	Lmotommu4		| no, skip
1970	movl	sp@(4),a0
1971	movc	dfc,d1
1972	moveq	#1,d0			| user space
1973	movc	d0,dfc
1974	.word	0xf508			| pflush a0@
1975	moveq	#5,d0			| super space
1976	movc	d0,dfc
1977	.word	0xf508			| pflush a0@
1978	movc	d1,dfc
1979	rts
1980Lmotommu4:
1981#endif
1982#if defined(HP330) || defined(HP360) || defined(HP370)
1983	tstl	_mmutype		| HP MMU?
1984	jeq	Lhpmmu5			| yes, skip
1985	movl	sp@(4),a0		| get addr to flush
1986#if defined(HP360) || defined(HP370)
1987	jpl	Lmc68851b		| is 68851?
1988	pflush	#0,#0,a0@		| flush address from both sides
1989	movl	#DC_CLEAR,d0
1990	movc	d0,cacr			| invalidate on-chip data cache
1991	rts
1992Lmc68851b:
1993#endif
1994	pflushs	#0,#0,a0@		| flush address from both sides
1995	rts
1996Lhpmmu5:
1997#endif
1998#if defined(HP320) || defined(HP350)
1999	movl	sp@(4),d0		| VA to invalidate
2000	bclr	#0,d0			| ensure even
2001	movl	d0,a0
2002	movw	sr,d1			| go critical
2003	movw	#PSL_HIGHIPL,sr		|   while in purge space
2004	moveq	#FC_PURGE,d0		| change address space
2005	movc	d0,dfc			|   for destination
2006	moveq	#0,d0			| zero to invalidate?
2007	movsl	d0,a0@			| hit it
2008	moveq	#FC_USERD,d0		| back to old
2009	movc	d0,dfc			|   address space
2010	movw	d1,sr			| restore IPL
2011#endif
2012	rts
2013
2014/*
2015 * Invalidate supervisor side of TLB
2016 */
2017ENTRY(TBIAS)
2018#ifdef DEBUG
2019	tstl	fulltflush		| being conservative?
2020	jne	__TBIA			| yes, flush everything
2021#endif
2022#if defined(HP380)
2023	cmpl	#-2,_mmutype		| 68040?
2024	jne	Lmotommu5		| no, skip
2025	.word	0xf518			| yes, pflusha (for now) XXX
2026	rts
2027Lmotommu5:
2028#endif
2029#if defined(HP330) || defined(HP360) || defined(HP370)
2030	tstl	_mmutype		| HP MMU?
2031	jeq	Lhpmmu7			| yes, skip
2032#if defined(HP360) || defined(HP370)
2033	jpl	Lmc68851c		| 68851?
2034	pflush #4,#4			| flush supervisor TLB entries
2035	movl	#DC_CLEAR,d0
2036	movc	d0,cacr			| invalidate on-chip d-cache
2037	rts
2038Lmc68851c:
2039#endif
2040	pflushs #4,#4			| flush supervisor TLB entries
2041	rts
2042Lhpmmu7:
2043#endif
2044#if defined(HP320) || defined(HP350)
2045	MMUADDR(a0)
2046	movl	#0x8000,d0		| more
2047	movl	d0,a0@(MMUTBINVAL)	|   HP magic
2048#ifdef DEBUG
2049	tstl	fullcflush
2050	jne	__DCIS			| XXX: invalidate entire sup. cache
2051#endif
2052#endif
2053	rts
2054
2055/*
2056 * Invalidate user side of TLB
2057 */
2058ENTRY(TBIAU)
2059#ifdef DEBUG
2060	tstl	fulltflush		| being conservative?
2061	jne	__TBIA			| yes, flush everything
2062#endif
2063#if defined(HP380)
2064	cmpl	#-2,_mmutype		| 68040?
2065	jne	Lmotommu6		| no, skip
2066	.word	0xf518			| yes, pflusha (for now) XXX
2067	rts
2068Lmotommu6:
2069#endif
2070#if defined(HP330) || defined(HP360) || defined(HP370)
2071	tstl	_mmutype		| HP MMU?
2072	jeq	Lhpmmu8			| yes, skip
2073#if defined(HP360) || defined(HP370)
2074	jpl	Lmc68851d		| 68851?
2075	pflush	#0,#4			| flush user TLB entries
2076	movl	#DC_CLEAR,d0
2077	movc	d0,cacr			| invalidate on-chip d-cache
2078	rts
2079Lmc68851d:
2080#endif
2081	pflushs	#0,#4			| flush user TLB entries
2082	rts
2083Lhpmmu8:
2084#endif
2085#if defined(HP320) || defined(HP350)
2086	MMUADDR(a0)
2087	moveq	#0,d0			| more
2088	movl	d0,a0@(MMUTBINVAL)	|   HP magic
2089#ifdef DEBUG
2090	tstl	fullcflush
2091	jne	__DCIU			| XXX: invalidate entire user cache
2092#endif
2093#endif
2094	rts
2095
2096/*
2097 * Invalidate instruction cache
2098 */
2099ENTRY(ICIA)
2100#if defined(HP380)
2101ENTRY(ICPA)
2102	cmpl	#-2,_mmutype		| 68040
2103	jne	Lmotommu7		| no, skip
2104	.word	0xf498			| cinva ic
2105	rts
2106Lmotommu7:
2107#endif
2108	movl	#IC_CLEAR,d0
2109	movc	d0,cacr			| invalidate i-cache
2110	rts
2111
2112/*
2113 * Invalidate data cache.
2114 * HP external cache allows for invalidation of user/supervisor portions.
2115 * NOTE: we do not flush 68030 on-chip cache as there are no aliasing
2116 * problems with DC_WA.  The only cases we have to worry about are context
2117 * switch and TLB changes, both of which are handled "in-line" in resume
2118 * and TBI*.
2119 */
2120ENTRY(DCIA)
2121__DCIA:
2122#if defined(HP380)
2123	cmpl	#-2,_mmutype		| 68040
2124	jne	Lmotommu8		| no, skip
2125	/* XXX implement */
2126	rts
2127Lmotommu8:
2128#endif
2129#if defined(HP320) || defined(HP350)
2130	tstl	_ectype			| got external VAC?
2131	jle	Lnocache2		| no, all done
2132	MMUADDR(a0)
2133	andl	#~MMU_CEN,a0@(MMUCMD)	| disable cache in MMU control reg
2134	orl	#MMU_CEN,a0@(MMUCMD)	| reenable cache in MMU control reg
2135Lnocache2:
2136#endif
2137	rts
2138
2139ENTRY(DCIS)
2140__DCIS:
2141#if defined(HP380)
2142	cmpl	#-2,_mmutype		| 68040
2143	jne	Lmotommu9		| no, skip
2144	/* XXX implement */
2145	rts
2146Lmotommu9:
2147#endif
2148#if defined(HP320) || defined(HP350)
2149	tstl	_ectype			| got external VAC?
2150	jle	Lnocache3		| no, all done
2151	MMUADDR(a0)
2152	movl	a0@(MMUSSTP),d0		| read the supervisor STP
2153	movl	d0,a0@(MMUSSTP)		| write it back
2154Lnocache3:
2155#endif
2156	rts
2157
2158ENTRY(DCIU)
2159__DCIU:
2160#if defined(HP380)
2161	cmpl	#-2,_mmutype		| 68040
2162	jne	LmotommuA		| no, skip
2163	/* XXX implement */
2164	rts
2165LmotommuA:
2166#endif
2167#if defined(HP320) || defined(HP350)
2168	tstl	_ectype			| got external VAC?
2169	jle	Lnocache4		| no, all done
2170	MMUADDR(a0)
2171	movl	a0@(MMUUSTP),d0		| read the user STP
2172	movl	d0,a0@(MMUUSTP)		| write it back
2173Lnocache4:
2174#endif
2175	rts
2176
2177#if defined(HP380)
2178ENTRY(ICPL)
2179	movl	sp@(4),a0		| address
2180	.word	0xf488			| cinvl ic,a0@
2181	rts
2182ENTRY(ICPP)
2183	movl	sp@(4),a0		| address
2184	.word	0xf490			| cinvp ic,a0@
2185	rts
2186ENTRY(DCPL)
2187	movl	sp@(4),a0		| address
2188	.word	0xf448			| cinvl dc,a0@
2189	rts
2190ENTRY(DCPP)
2191	movl	sp@(4),a0		| address
2192	.word	0xf450			| cinvp dc,a0@
2193	rts
2194ENTRY(DCPA)
2195	.word	0xf458			| cinva dc
2196	rts
2197ENTRY(DCFL)
2198	movl	sp@(4),a0		| address
2199	.word	0xf468			| cpushl dc,a0@
2200	rts
2201ENTRY(DCFP)
2202	movl	sp@(4),a0		| address
2203	.word	0xf470			| cpushp dc,a0@
2204	rts
2205#endif
2206
2207ENTRY(PCIA)
2208#if defined(HP380)
2209ENTRY(DCFA)
2210	cmpl	#-2,_mmutype		| 68040
2211	jne	LmotommuB		| no, skip
2212	.word	0xf478			| cpusha dc
2213	rts
2214LmotommuB:
2215#endif
2216#if defined(HP360) || defined(HP370)
2217	movl	#DC_CLEAR,d0
2218	movc	d0,cacr			| invalidate on-chip d-cache
2219	tstl	_ectype			| got external PAC?
2220	jge	Lnocache6		| no, all done
2221	MMUADDR(a0)
2222	andl	#~MMU_CEN,a0@(MMUCMD)	| disable cache in MMU control reg
2223	orl	#MMU_CEN,a0@(MMUCMD)	| reenable cache in MMU control reg
2224Lnocache6:
2225#endif
2226	rts
2227
2228ENTRY(ecacheon)
2229	tstl	_ectype
2230	jeq	Lnocache7
2231	MMUADDR(a0)
2232	orl	#MMU_CEN,a0@(MMUCMD)
2233Lnocache7:
2234	rts
2235
2236ENTRY(ecacheoff)
2237	tstl	_ectype
2238	jeq	Lnocache8
2239	MMUADDR(a0)
2240	andl	#~MMU_CEN,a0@(MMUCMD)
2241Lnocache8:
2242	rts
2243
2244/*
2245 * Get callers current SP value.
2246 * Note that simply taking the address of a local variable in a C function
2247 * doesn't work because callee saved registers may be outside the stack frame
2248 * defined by A6 (e.g. GCC generated code).
2249 */
2250	.globl	_getsp
2251_getsp:
2252	movl	sp,d0			| get current SP
2253	addql	#4,d0			| compensate for return address
2254	rts
2255
2256	.globl	_getsfc, _getdfc
2257_getsfc:
2258	movc	sfc,d0
2259	rts
2260_getdfc:
2261	movc	dfc,d0
2262	rts
2263
2264/*
2265 * Load a new user segment table pointer.
2266 */
2267ENTRY(loadustp)
2268#if defined(HP330) || defined(HP360) || defined(HP370) || defined(HP380)
2269	tstl	_mmutype		| HP MMU?
2270	jeq	Lhpmmu9			| yes, skip
2271	movl	sp@(4),d0		| new USTP
2272	moveq	#PGSHIFT,d1
2273	lsll	d1,d0			| convert to addr
2274#if defined(HP380)
2275	cmpl	#-2,_mmutype		| 68040?
2276	jne	LmotommuC		| no, skip
2277	.long	0x4e7b0806		| movc d0,urp
2278	rts
2279LmotommuC:
2280#endif
2281	lea	_protorp,a0		| CRP prototype
2282	movl	d0,a0@(4)		| stash USTP
2283	pmove	a0@,crp			| load root pointer
2284	movl	#DC_CLEAR,d0
2285	movc	d0,cacr			| invalidate on-chip d-cache
2286	rts				|   since pmove flushes TLB
2287Lhpmmu9:
2288#endif
2289#if defined(HP320) || defined(HP350)
2290	MMUADDR(a0)
2291	movl	sp@(4),a0@(MMUUSTP)	| load a new USTP
2292#endif
2293	rts
2294
2295ENTRY(ploadw)
2296#if defined(HP330) || defined(HP360) || defined(HP370)
2297	movl	sp@(4),a0		| address to load
2298	ploadw	#1,a0@			| pre-load translation
2299#endif
2300	rts
2301
2302/*
2303 * Set processor priority level calls.  Most are implemented with
2304 * inline asm expansions.  However, spl0 requires special handling
2305 * as we need to check for our emulated software interrupts.
2306 */
2307
2308ENTRY(spl0)
2309	moveq	#0,d0
2310	movw	sr,d0			| get old SR for return
2311	movw	#PSL_LOWIPL,sr		| restore new SR
2312	tstb	_ssir			| software interrupt pending?
2313	jeq	Lspldone		| no, all done
2314	subql	#4,sp			| make room for RTE frame
2315	movl	sp@(4),sp@(2)		| position return address
2316	clrw	sp@(6)			| set frame type 0
2317	movw	#PSL_LOWIPL,sp@		| and new SR
2318	jra	Lgotsir			| go handle it
2319Lspldone:
2320	rts
2321
2322ENTRY(_insque)
2323	movw	sr,d0
2324	movw	#PSL_HIGHIPL,sr		| atomic
2325	movl	sp@(8),a0		| where to insert (after)
2326	movl	sp@(4),a1		| element to insert (e)
2327	movl	a0@,a1@			| e->next = after->next
2328	movl	a0,a1@(4)		| e->prev = after
2329	movl	a1,a0@			| after->next = e
2330	movl	a1@,a0
2331	movl	a1,a0@(4)		| e->next->prev = e
2332	movw	d0,sr
2333	rts
2334
2335ENTRY(_remque)
2336	movw	sr,d0
2337	movw	#PSL_HIGHIPL,sr		| atomic
2338	movl	sp@(4),a0		| element to remove (e)
2339	movl	a0@,a1
2340	movl	a0@(4),a0
2341	movl	a0,a1@(4)		| e->next->prev = e->prev
2342	movl	a1,a0@			| e->prev->next = e->next
2343	movw	d0,sr
2344	rts
2345
2346/*
2347 * bzero(addr, count)
2348 */
2349ALTENTRY(blkclr, _bzero)
2350ENTRY(bzero)
2351	movl	sp@(4),a0	| address
2352	movl	sp@(8),d0	| count
2353	jeq	Lbzdone		| if zero, nothing to do
2354	movl	a0,d1
2355	btst	#0,d1		| address odd?
2356	jeq	Lbzeven		| no, can copy words
2357	clrb	a0@+		| yes, zero byte to get to even boundary
2358	subql	#1,d0		| decrement count
2359	jeq	Lbzdone		| none left, all done
2360Lbzeven:
2361	movl	d0,d1
2362	andl	#31,d0
2363	lsrl	#5,d1		| convert count to 8*longword count
2364	jeq	Lbzbyte		| no such blocks, zero byte at a time
2365Lbzloop:
2366	clrl	a0@+; clrl	a0@+; clrl	a0@+; clrl	a0@+;
2367	clrl	a0@+; clrl	a0@+; clrl	a0@+; clrl	a0@+;
2368	subql	#1,d1		| one more block zeroed
2369	jne	Lbzloop		| more to go, do it
2370	tstl	d0		| partial block left?
2371	jeq	Lbzdone		| no, all done
2372Lbzbyte:
2373	clrb	a0@+
2374	subql	#1,d0		| one more byte cleared
2375	jne	Lbzbyte		| more to go, do it
2376Lbzdone:
2377	rts
2378
2379/*
2380 * strlen(str)
2381 */
2382ENTRY(strlen)
2383	moveq	#-1,d0
2384	movl	sp@(4),a0	| string
2385Lslloop:
2386	addql	#1,d0		| increment count
2387	tstb	a0@+		| null?
2388	jne	Lslloop		| no, keep going
2389	rts
2390
2391/*
2392 * bcmp(s1, s2, len)
2393 *
2394 * WARNING!  This guy only works with counts up to 64K
2395 */
2396ENTRY(bcmp)
2397	movl	sp@(4),a0		| string 1
2398	movl	sp@(8),a1		| string 2
2399	moveq	#0,d0
2400	movw	sp@(14),d0		| length
2401	jeq	Lcmpdone		| if zero, nothing to do
2402	subqw	#1,d0			| set up for DBcc loop
2403Lcmploop:
2404	cmpmb	a0@+,a1@+		| equal?
2405	dbne	d0,Lcmploop		| yes, keep going
2406	addqw	#1,d0			| +1 gives zero on match
2407Lcmpdone:
2408	rts
2409
2410/*
2411 * {ov}bcopy(from, to, len)
2412 *
2413 * Works for counts up to 128K.
2414 */
2415ALTENTRY(ovbcopy, _bcopy)
2416ENTRY(bcopy)
2417	movl	sp@(12),d0		| get count
2418	jeq	Lcpyexit		| if zero, return
2419	movl	sp@(4),a0		| src address
2420	movl	sp@(8),a1		| dest address
2421	cmpl	a1,a0			| src before dest?
2422	jlt	Lcpyback		| yes, copy backwards (avoids overlap)
2423	movl	a0,d1
2424	btst	#0,d1			| src address odd?
2425	jeq	Lcfeven			| no, go check dest
2426	movb	a0@+,a1@+		| yes, copy a byte
2427	subql	#1,d0			| update count
2428	jeq	Lcpyexit		| exit if done
2429Lcfeven:
2430	movl	a1,d1
2431	btst	#0,d1			| dest address odd?
2432	jne	Lcfbyte			| yes, must copy by bytes
2433	movl	d0,d1			| no, get count
2434	lsrl	#2,d1			| convert to longwords
2435	jeq	Lcfbyte			| no longwords, copy bytes
2436	subql	#1,d1			| set up for dbf
2437Lcflloop:
2438	movl	a0@+,a1@+		| copy longwords
2439	dbf	d1,Lcflloop		| til done
2440	andl	#3,d0			| get remaining count
2441	jeq	Lcpyexit		| done if none
2442Lcfbyte:
2443	subql	#1,d0			| set up for dbf
2444Lcfbloop:
2445	movb	a0@+,a1@+		| copy bytes
2446	dbf	d0,Lcfbloop		| til done
2447Lcpyexit:
2448	rts
2449Lcpyback:
2450	addl	d0,a0			| add count to src
2451	addl	d0,a1			| add count to dest
2452	movl	a0,d1
2453	btst	#0,d1			| src address odd?
2454	jeq	Lcbeven			| no, go check dest
2455	movb	a0@-,a1@-		| yes, copy a byte
2456	subql	#1,d0			| update count
2457	jeq	Lcpyexit		| exit if done
2458Lcbeven:
2459	movl	a1,d1
2460	btst	#0,d1			| dest address odd?
2461	jne	Lcbbyte			| yes, must copy by bytes
2462	movl	d0,d1			| no, get count
2463	lsrl	#2,d1			| convert to longwords
2464	jeq	Lcbbyte			| no longwords, copy bytes
2465	subql	#1,d1			| set up for dbf
2466Lcblloop:
2467	movl	a0@-,a1@-		| copy longwords
2468	dbf	d1,Lcblloop		| til done
2469	andl	#3,d0			| get remaining count
2470	jeq	Lcpyexit		| done if none
2471Lcbbyte:
2472	subql	#1,d0			| set up for dbf
2473Lcbbloop:
2474	movb	a0@-,a1@-		| copy bytes
2475	dbf	d0,Lcbbloop		| til done
2476	rts
2477
2478/*
2479 * Emulate fancy VAX string operations:
2480 *	scanc(count, startc, table, mask)
2481 *	skpc(mask, count, startc)
2482 *	locc(mask, count, startc)
2483 */
2484ENTRY(scanc)
2485	movl	sp@(4),d0	| get length
2486	jeq	Lscdone		| nothing to do, return
2487	movl	sp@(8),a0	| start of scan
2488	movl	sp@(12),a1	| table to compare with
2489	movb	sp@(19),d1	| and mask to use
2490	movw	d2,sp@-		| need a scratch register
2491	clrw	d2		| clear it out
2492	subqw	#1,d0		| adjust for dbra
2493Lscloop:
2494	movb	a0@+,d2		| get character
2495	movb	a1@(0,d2:w),d2	| get table entry
2496	andb	d1,d2		| mask it
2497	dbne	d0,Lscloop	| keep going til no more or non-zero
2498	addqw	#1,d0		| overshot by one
2499	movw	sp@+,d2		| restore scratch
2500Lscdone:
2501	rts
2502
2503ENTRY(skpc)
2504	movl	sp@(8),d0	| get length
2505	jeq	Lskdone		| nothing to do, return
2506	movb	sp@(7),d1	| mask to use
2507	movl	sp@(12),a0	| where to start
2508	subqw	#1,d0		| adjust for dbcc
2509Lskloop:
2510	cmpb	a0@+,d1		| compate with mask
2511	dbne	d0,Lskloop	| keep going til no more or zero
2512	addqw	#1,d0		| overshot by one
2513Lskdone:
2514	rts
2515
2516ENTRY(locc)
2517	movl	sp@(8),d0	| get length
2518	jeq	Llcdone		| nothing to do, return
2519	movb	sp@(7),d1	| mask to use
2520	movl	sp@(12),a0	| where to start
2521	subqw	#1,d0		| adjust for dbcc
2522Llcloop:
2523	cmpb	a0@+,d1		| compate with mask
2524	dbeq	d0,Llcloop	| keep going til no more or non-zero
2525	addqw	#1,d0		| overshot by one
2526Llcdone:
2527	rts
2528
2529/*
2530 * Emulate VAX FFS (find first set) instruction.
2531 */
2532ENTRY(ffs)
2533	moveq	#-1,d0
2534	movl	sp@(4),d1
2535	jeq	Lffsdone
2536Lffsloop:
2537	addql	#1,d0
2538	btst	d0,d1
2539	jeq	Lffsloop
2540Lffsdone:
2541	addql	#1,d0
2542	rts
2543
2544#ifdef FPCOPROC
2545/*
2546 * Save and restore 68881 state.
2547 * Pretty awful looking since our assembler does not
2548 * recognize FP mnemonics.
2549 */
2550ENTRY(m68881_save)
2551	movl	sp@(4),a0		| save area pointer
2552	fsave	a0@			| save state
2553	tstb	a0@			| null state frame?
2554	jeq	Lm68881sdone		| yes, all done
2555	fmovem fp0-fp7,a0@(216)		| save FP general registers
2556	fmovem fpcr/fpsr/fpi,a0@(312)	| save FP control registers
2557Lm68881sdone:
2558	rts
2559
2560ENTRY(m68881_restore)
2561	movl	sp@(4),a0		| save area pointer
2562	tstb	a0@			| null state frame?
2563	jeq	Lm68881rdone		| yes, easy
2564	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
2565	fmovem	a0@(216),fp0-fp7	| restore FP general registers
2566Lm68881rdone:
2567	frestore a0@			| restore state
2568	rts
2569#endif
2570
2571/*
2572 * Handle the nitty-gritty of rebooting the machine.
2573 * Basically we just turn off the MMU and jump to the appropriate ROM routine.
2574 * Note that we must be running in an address range that is mapped one-to-one
2575 * logical to physical so that the PC is still valid immediately after the MMU
2576 * is turned off.  We have conveniently mapped the last page of physical
2577 * memory this way.
2578 */
2579	.globl	_doboot
2580_doboot:
2581#if defined(HP380)
2582	cmpl	#-2,_mmutype		| 68040?
2583	jeq	Lnocache5		| yes, skip
2584#endif
2585	movl	#CACHE_OFF,d0
2586	movc	d0,cacr			| disable on-chip cache(s)
2587#if defined(HP320) || defined(HP350) || defined(HP370)
2588	tstl	_ectype
2589	jeq	Lnocache5
2590	MMUADDR(a0)
2591	andl	#~MMU_CEN,a0@(MMUCMD)	| disable external cache
2592#endif
2593Lnocache5:
2594	lea	MAXADDR,a0		| last page of physical memory
2595	movl	_boothowto,a0@+		| store howto
2596	movl	_bootdev,a0@+		| and devtype
2597	lea	Lbootcode,a1		| start of boot code
2598	lea	Lebootcode,a3		| end of boot code
2599Lbootcopy:
2600	movw	a1@+,a0@+		| copy a word
2601	cmpl	a3,a1			| done yet?
2602	jcs	Lbootcopy		| no, keep going
2603#if defined(HP380)
2604	cmpl	#-2,_mmutype		| 68040?
2605	jne	LmotommuE		| no, skip
2606	.word	0xf4f8			| cpusha bc
2607LmotommuE:
2608#endif
2609	jmp	MAXADDR+8		| jump to last page
2610
2611Lbootcode:
2612	lea	MAXADDR+0x800,sp	| physical SP in case of NMI
2613#if defined(HP380)
2614	cmpl	#-2,_mmutype		| 68040?
2615	jne	LmotommuF		| no, skip
2616	movl	#0,d0
2617	movc	d0,cacr			| caches off
2618	.long	0x4e7b0003		| movc d0,tc
2619	movl	d2,MAXADDR+NBPG-4	| restore old high page contents
2620	jmp	0x1A4			| goto REQ_REBOOT
2621LmotommuF:
2622#endif
2623#if defined(HP330) || defined(HP360) || defined(HP370)
2624	tstl	_mmutype		| HP MMU?
2625	jeq	LhpmmuB			| yes, skip
2626	movl	#0,a0@			| value for pmove to TC (turn off MMU)
2627	pmove	a0@,tc			| disable MMU
2628	jmp	0x1A4			| goto REQ_REBOOT
2629LhpmmuB:
2630#endif
2631#if defined(HP320) || defined(HP350)
2632	MMUADDR(a0)
2633	movl	#0xFFFF0000,a0@(MMUCMD)	| totally disable MMU
2634	movl	d2,MAXADDR+NBPG-4	| restore old high page contents
2635	jmp	0x1A4			| goto REQ_REBOOT
2636#endif
2637Lebootcode:
2638
2639	.data
2640	.globl	_machineid
2641_machineid:
2642	.long	0		| default to 320
2643	.globl	_mmutype,_protorp
2644_mmutype:
2645	.long	0		| default to HP MMU
2646_protorp:
2647	.long	0,0		| prototype root pointer
2648	.globl	_ectype
2649_ectype:
2650	.long	0		| external cache type, default to none
2651	.globl	_internalhpib
2652_internalhpib:
2653	.long	1		| has internal HP-IB, default to yes
2654	.globl	_cold
2655_cold:
2656	.long	1		| cold start flag
2657	.globl	_want_resched
2658_want_resched:
2659	.long	0
2660	.globl	_intiobase, _intiolimit, _extiobase, _CLKbase, _MMUbase
2661	.globl	_proc0paddr
2662_proc0paddr:
2663	.long	0		| KVA of proc0 u-area
2664_intiobase:
2665	.long	0		| KVA of base of internal IO space
2666_intiolimit:
2667	.long	0		| KVA of end of internal IO space
2668_extiobase:
2669	.long	0		| KVA of base of external IO space
2670_CLKbase:
2671	.long	0		| KVA of base of clock registers
2672_MMUbase:
2673	.long	0		| KVA of base of HP MMU registers
2674#ifdef USELEDS
2675heartbeat:
2676	.long	0		| clock ticks since last pulse of heartbeat
2677#endif
2678#ifdef DEBUG
2679	.globl	fulltflush, fullcflush
2680fulltflush:
2681	.long	0
2682fullcflush:
2683	.long	0
2684#endif
2685#ifdef HPFPLIB
2686/*
2687 * Undefined symbols from hpux_float.o:
2688 *
2689 * kdb_printf:	A kernel debugger print routine, we just use printf instead.
2690 * processor:	HP-UX equiv. of machineid, set to 3 if it is a 68040.
2691 * u:		Ye ole u-area.  The code wants to grab the first longword
2692 *		indirect off of that and clear the 0x40000 bit there.
2693 *		Oddly enough this was incorrect even in HP-UX!
2694 * runrun:	Old name for want_resched.
2695 */
2696	.globl	_kdb_printf,_processor,_u,_runrun
2697_kdb_printf:
2698	.long	_printf
2699_processor:
2700	.long	0
2701_u:
2702	.long	.+4
2703	.long	0
2704	.set	_runrun,_want_resched
2705#endif
2706/* interrupt counters */
2707	.globl	_intrcnt,_eintrcnt,_intrnames,_eintrnames
2708_intrnames:
2709	.asciz	"spur"
2710	.asciz	"hil"
2711	.asciz	"lev2"
2712	.asciz	"lev3"
2713	.asciz	"lev4"
2714	.asciz	"lev5"
2715	.asciz	"dma"
2716	.asciz	"clock"
2717	.asciz  "statclock"
2718	.asciz	"nmi"
2719_eintrnames:
2720	.even
2721_intrcnt:
2722	.long	0,0,0,0,0,0,0,0,0,0
2723_eintrcnt:
2724