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