xref: /original-bsd/sys/hp300/hp300/locore.s (revision 044d1bee)
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.21 (Berkeley) 12/30/92
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	lea	sp@(16),a1		| a1 = &clockframe
621	movb	a0@(CLKSR),d0		| read clock status
622	btst	#2,d0			| timer3 interrupt?
623	jeq	1f			| no, skip statintr
624	movb	a0@(CLKMSB3),d1		| clear timer3 interrupt
625	addql	#1,_intrcnt+32		| count statclock interrupts
626	movl	d0,sp@-			| save status
627	movl	a1,sp@-
628	jbsr	_statintr		| statintr(&frame)
629	addql	#4,sp
630	movl	sp@+,d0			| restore status
631	CLKADDR(a0)
632	lea	sp@(16),a1
6331:
634	btst	#0,d0			| timer1 interrupt?
635	jeq	2f			| no, skip hardclock
636	movb	a0@(CLKMSB1),d1		| clear timer1 interrupt
637	addql	#1,_intrcnt+28		| count hardclock interrupts
638	movl	a1,sp@-
639#ifdef USELEDS
640	.globl	_ledaddr, _inledcontrol, _ledcontrol, _hz
641	tstl	_ledaddr		| using LEDs?
642	jeq	Lnoled0			| no, skip this code
643	movl	heartbeat,d0		| get tick count
644	addql	#1,d0			|  increment
645	movl	_hz,d1
646	lsrl	#1,d1			| throb twice a second
647	cmpl	d0,d1			| are we there yet?
648	jne	Lnoled1			| no, nothing to do
649	tstl	_inledcontrol		| already updating LEDs?
650	jne	Lnoled2			| yes, skip it
651	movl	#LED_PULSE,sp@-
652	movl	#LED_DISK+LED_LANRCV+LED_LANXMT,sp@-
653	clrl	sp@-
654	jbsr	_ledcontrol		| toggle pulse, turn all others off
655	lea	sp@(12),sp
656Lnoled2:
657	movql	#0,d0
658Lnoled1:
659	movl	d0,heartbeat
660Lnoled0:
661#endif
662	jbsr	_hardclock		| hardclock(&frame)
663	addql	#4,sp
6642:
665	moveml	sp@+,#0x0303		| restore scratch registers
666	addql	#1,_cnt+V_INTR		| chalk up another interrupt
667	jra	rei			| all done
668
669_lev7intr:
670	addql	#1,_intrcnt+36
671	clrl	sp@-
672	moveml	#0xFFFF,sp@-		| save registers
673	movl	usp,a0			| and save
674	movl	a0,sp@(FR_SP)		|   the user stack pointer
675	jbsr	_nmihand		| call handler
676	movl	sp@(FR_SP),a0		| restore
677	movl	a0,usp			|   user SP
678	moveml	sp@+,#0x7FFF		| and remaining registers
679	addql	#8,sp			| pop SP and stack adjust
680	jra	rei			| all done
681
682/*
683 * Emulation of VAX REI instruction.
684 *
685 * This code deals with checking for and servicing ASTs
686 * (profiling, scheduling) and software interrupts (network, softclock).
687 * We check for ASTs first, just like the VAX.  To avoid excess overhead
688 * the T_ASTFLT handling code will also check for software interrupts so we
689 * do not have to do it here.  After identifing that we need an AST we
690 * drop the IPL to allow device interrupts.
691 *
692 * This code is complicated by the fact that sendsig may have been called
693 * necessitating a stack cleanup.
694 */
695	.comm	_ssir,1
696	.globl	_astpending
697rei:
698#ifdef STACKCHECK
699	tstl	_panicstr		| have we paniced?
700	jne	Ldorte1			| yes, do not make matters worse
701#endif
702	tstl	_astpending		| AST pending?
703	jeq	Lchksir			| no, go check for SIR
704Lrei1:
705	btst	#5,sp@			| yes, are we returning to user mode?
706	jne	Lchksir			| no, go check for SIR
707	movw	#PSL_LOWIPL,sr		| lower SPL
708	clrl	sp@-			| stack adjust
709	moveml	#0xFFFF,sp@-		| save all registers
710	movl	usp,a1			| including
711	movl	a1,sp@(FR_SP)		|    the users SP
712	clrl	sp@-			| VA == none
713	clrl	sp@-			| code == none
714	movl	#T_ASTFLT,sp@-		| type == async system trap
715	jbsr	_trap			| go handle it
716	lea	sp@(12),sp		| pop value args
717	movl	sp@(FR_SP),a0		| restore user SP
718	movl	a0,usp			|   from save area
719	movw	sp@(FR_ADJ),d0		| need to adjust stack?
720	jne	Laststkadj		| yes, go to it
721	moveml	sp@+,#0x7FFF		| no, restore most user regs
722	addql	#8,sp			| toss SP and stack adjust
723#ifdef STACKCHECK
724	jra	Ldorte
725#else
726	rte				| and do real RTE
727#endif
728Laststkadj:
729	lea	sp@(FR_HW),a1		| pointer to HW frame
730	addql	#8,a1			| source pointer
731	movl	a1,a0			| source
732	addw	d0,a0			|  + hole size = dest pointer
733	movl	a1@-,a0@-		| copy
734	movl	a1@-,a0@-		|  8 bytes
735	movl	a0,sp@(FR_SP)		| new SSP
736	moveml	sp@+,#0x7FFF		| restore user registers
737	movl	sp@,sp			| and our SP
738#ifdef STACKCHECK
739	jra	Ldorte
740#else
741	rte				| and do real RTE
742#endif
743Lchksir:
744	tstb	_ssir			| SIR pending?
745	jeq	Ldorte			| no, all done
746	movl	d0,sp@-			| need a scratch register
747	movw	sp@(4),d0		| get SR
748	andw	#PSL_IPL7,d0		| mask all but IPL
749	jne	Lnosir			| came from interrupt, no can do
750	movl	sp@+,d0			| restore scratch register
751Lgotsir:
752	movw	#SPL1,sr		| prevent others from servicing int
753	tstb	_ssir			| too late?
754	jeq	Ldorte			| yes, oh well...
755	clrl	sp@-			| stack adjust
756	moveml	#0xFFFF,sp@-		| save all registers
757	movl	usp,a1			| including
758	movl	a1,sp@(FR_SP)		|    the users SP
759	clrl	sp@-			| VA == none
760	clrl	sp@-			| code == none
761	movl	#T_SSIR,sp@-		| type == software interrupt
762	jbsr	_trap			| go handle it
763	lea	sp@(12),sp		| pop value args
764	movl	sp@(FR_SP),a0		| restore
765	movl	a0,usp			|   user SP
766	moveml	sp@+,#0x7FFF		| and all remaining registers
767	addql	#8,sp			| pop SP and stack adjust
768#ifdef STACKCHECK
769	jra	Ldorte
770#else
771	rte
772#endif
773Lnosir:
774	movl	sp@+,d0			| restore scratch register
775Ldorte:
776#ifdef STACKCHECK
777	movw	#SPL6,sr		| avoid trouble
778	btst	#5,sp@			| are we returning to user mode?
779	jne	Ldorte1			| no, skip it
780	movl	a6,tmpstk-20
781	movl	d0,tmpstk-76
782	moveq	#0,d0
783	movb	sp@(6),d0		| get format/vector
784	lsrl	#3,d0			| convert to index
785	lea	_exframesize,a6		|  into exframesize
786	addl	d0,a6			|  to get pointer to correct entry
787	movw	a6@,d0			| get size for this frame
788	addql	#8,d0			| adjust for unaccounted for bytes
789	lea	_kstackatbase,a6	| desired stack base
790	subl	d0,a6			|   - frame size == our stack
791	cmpl	a6,sp			| are we where we think?
792	jeq	Ldorte2			| yes, skip it
793	lea	tmpstk,a6		| will be using tmpstk
794	movl	sp@(4),a6@-		| copy common
795	movl	sp@,a6@-		|   frame info
796	clrl	a6@-
797	movl	sp,a6@-			| save sp
798	subql	#4,a6			| skip over already saved a6
799	moveml	#0x7FFC,a6@-		| push remaining regs (d0/a6/a7 done)
800	lea	a6@(-4),sp		| switch to tmpstk (skip saved d0)
801	clrl	sp@-			| is an underflow
802	jbsr	_badkstack		| badkstack(0, frame)
803	addql	#4,sp
804	moveml	sp@+,#0x7FFF		| restore most registers
805	movl	sp@,sp			| and SP
806	rte
807Ldorte2:
808	movl	tmpstk-76,d0
809	movl	tmpstk-20,a6
810Ldorte1:
811#endif
812	rte				| real return
813
814/*
815 * Kernel access to the current processes kernel stack is via a fixed
816 * virtual address.  It is at the same address as in the users VA space.
817 * Umap contains the KVA of the first of UPAGES PTEs mapping VA _kstack.
818 */
819	.data
820	.set	_kstack,USRSTACK
821	.set	_kstackatbase,USRSTACK+UPAGES*NBPG-4
822	.globl	_kstackatbase
823_Umap:	.long	0
824	.globl	_kstack, _Umap
825
826#define	RELOC(var, ar)	\
827	lea	var,ar;	\
828	addl	a5,ar
829
830/*
831 * Initialization
832 *
833 * A5 contains physical load point from boot
834 * VBR contains zero from ROM.  Exceptions will continue to vector
835 * through ROM until MMU is turned on at which time they will vector
836 * through our table (vectors.s).
837 */
838	.comm	_lowram,4
839
840	.text
841	.globl	_edata
842	.globl	_etext,_end
843	.globl	start
844start:
845	movw	#PSL_HIGHIPL,sr		| no interrupts
846	RELOC(tmpstk, a0)
847	movl	a0,sp			| give ourselves a temporary stack
848	RELOC(_lowram, a0)
849	movl	a5,a0@			| store start of physical memory
850	movl	#CACHE_OFF,d0
851	movc	d0,cacr			| clear and disable on-chip cache(s)
852
853/* determine our CPU/MMU combo - check for all regardless of kernel config */
854	movl	#INTIOBASE+MMUBASE,a1
855	movl	#0x200,d0		| data freeze bit
856	movc	d0,cacr			|   only exists on 68030
857	movc	cacr,d0			| read it back
858	tstl	d0			| zero?
859	jeq	Lnot68030		| yes, we have 68020/68040
860	RELOC(_mmutype, a0)		| no, we have 68030
861	movl	#-1,a0@			| set to reflect 68030 PMMU
862	RELOC(_machineid, a0)
863	movl	#0x80,a1@(MMUCMD)	| set magic cookie
864	movl	a1@(MMUCMD),d0		| read it back
865	btst	#7,d0			| cookie still on?
866	jeq	Lnot370			| no, 360 or 375
867	movl	#0,a1@(MMUCMD)		| clear magic cookie
868	movl	a1@(MMUCMD),d0		| read it back
869	btst	#7,d0			| still on?
870	jeq	Lisa370			| no, must be a 370
871	movl	#5,a0@			| yes, must be a 340
872	jra	Lstart1
873Lnot370:
874	movl	#3,a0@			| type is at least a 360
875	movl	#0,a1@(MMUCMD)		| clear magic cookie2
876	movl	a1@(MMUCMD),d0		| read it back
877	btst	#16,d0			| still on?
878	jeq	Lstart1			| no, must be a 360
879	movl	#6,a0@			| yes, must be a 345/375
880	jra	Lhaspac
881Lisa370:
882	movl	#4,a0@			| set to 370
883Lhaspac:
884	RELOC(_ectype, a0)
885	movl	#-1,a0@			| also has a physical address cache
886	jra	Lstart1
887Lnot68030:
888	bset	#31,d0			| data cache enable bit
889	movc	d0,cacr			|   only exists on 68040
890	movc	cacr,d0			| read it back
891	tstl	d0			| zero?
892	beq	Lis68020		| yes, we have 68020
893	moveq	#0,d0			| now turn it back off
894	movec	d0,cacr			|   before we access any data
895	RELOC(_mmutype, a0)
896	movl	#-2,a0@			| with a 68040 MMU
897	RELOC(_ectype, a0)
898	movl	#0,a0@			| and no cache (for now XXX)
899#ifdef HPFPLIB
900	RELOC(_processor, a0)
901	movl	#3,a0@			| HP-UX style processor id
902#endif
903	RELOC(_machineid, a0)
904	movl	a1@(MMUCMD),d0		| read MMU register
905	lsrl	#8,d0			| get apparent ID
906	cmpb	#6,d0			| id == 6?
907	jeq	Lis33mhz		| yes, we have a 433s
908	movl	#7,a0@			| no, we have a 380/425t
909	jra	Lstart1
910Lis33mhz:
911	movl	#8,a0@			| 433s (XXX 425s returns same ID, ugh!)
912	jra	Lstart1
913Lis68020:
914	movl	#1,a1@(MMUCMD)		| a 68020, write HP MMU location
915	movl	a1@(MMUCMD),d0		| read it back
916	btst	#0,d0			| non-zero?
917	jne	Lishpmmu		| yes, we have HP MMU
918	RELOC(_mmutype, a0)
919	movl	#1,a0@			| no, we have PMMU
920	RELOC(_machineid, a0)
921	movl	#1,a0@			| and 330 CPU
922	jra	Lstart1
923Lishpmmu:
924	RELOC(_ectype, a0)		| 320 or 350
925	movl	#1,a0@			| both have a virtual address cache
926	movl	#0x80,a1@(MMUCMD)	| set magic cookie
927	movl	a1@(MMUCMD),d0		| read it back
928	btst	#7,d0			| cookie still on?
929	jeq	Lstart1			| no, just a 320
930	RELOC(_machineid, a0)
931	movl	#2,a0@			| yes, a 350
932
933Lstart1:
934	movl	#0,a1@(MMUCMD)		| clear out MMU again
935/* initialize source/destination control registers for movs */
936	moveq	#FC_USERD,d0		| user space
937	movc	d0,sfc			|   as source
938	movc	d0,dfc			|   and destination of transfers
939/* initialize memory sizes (for pmap_bootstrap) */
940	movl	#MAXADDR,d1		| last page
941	moveq	#PGSHIFT,d2
942	lsrl	d2,d1			| convert to page (click) number
943	RELOC(_maxmem, a0)
944	movl	d1,a0@			| save as maxmem
945	movl	a5,d0			| lowram value from ROM via boot
946	lsrl	d2,d0			| convert to page number
947	subl	d0,d1			| compute amount of RAM present
948	RELOC(_physmem, a0)
949	movl	d1,a0@			| and physmem
950/* configure kernel and proc0 VA space so we can get going */
951	.globl	_Sysseg, _pmap_bootstrap, _avail_start
952	movl	#_end,d5		| end of static kernel text/data
953	addl	#NBPG-1,d5
954	andl	#PG_FRAME,d5		| round to a page
955	movl	d5,a4
956	addl	a5,a4			| convert to PA
957	pea	a5@			| firstpa
958	pea	a4@			| nextpa
959	RELOC(_pmap_bootstrap,a0)
960	jbsr	a0@			| pmap_bootstrap(firstpa, nextpa)
961	addql	#8,sp
962
963/*
964 * Prepare to enable MMU.
965 * Since the kernel is not mapped logical == physical we must insure
966 * that when the MMU is turned on, all prefetched addresses (including
967 * the PC) are valid.  In order guarentee that, we use the last physical
968 * page (which is conveniently mapped == VA) and load it up with enough
969 * code to defeat the prefetch, then we execute the jump back to here.
970 *
971 * Is this all really necessary, or am I paranoid??
972 */
973	RELOC(_Sysseg, a0)		| system segment table addr
974	movl	a0@,d1			| read value (a KVA)
975	addl	a5,d1			| convert to PA
976	RELOC(_mmutype, a0)
977	tstl	a0@			| HP MMU?
978	jeq	Lhpmmu2			| yes, skip
979	cmpl	#-2,a0@			| 68040?
980	jne	Lmotommu1		| no, skip
981	.long	0x4e7b1807		| movc d1,srp
982	jra	Lstploaddone
983Lmotommu1:
984	RELOC(_protorp, a0)
985	movl	#0x80000202,a0@		| nolimit + share global + 4 byte PTEs
986	movl	d1,a0@(4)		| + segtable address
987	pmove	a0@,srp			| load the supervisor root pointer
988	movl	#0x80000002,a0@		| reinit upper half for CRP loads
989	jra	Lstploaddone		| done
990Lhpmmu2:
991	moveq	#PGSHIFT,d2
992	lsrl	d2,d1			| convert to page frame
993	movl	d1,INTIOBASE+MMUBASE+MMUSSTP | load in sysseg table register
994Lstploaddone:
995	lea	MAXADDR,a2		| PA of last RAM page
996	RELOC(Lhighcode, a1)		| addr of high code
997	RELOC(Lehighcode, a3)		| end addr
998Lcodecopy:
999	movw	a1@+,a2@+		| copy a word
1000	cmpl	a3,a1			| done yet?
1001	jcs	Lcodecopy		| no, keep going
1002	jmp	MAXADDR			| go for it!
1003
1004Lhighcode:
1005	RELOC(_mmutype, a0)
1006	tstl	a0@			| HP MMU?
1007	jeq	Lhpmmu3			| yes, skip
1008	cmpl	#-2,a0@			| 68040?
1009	jne	Lmotommu2		| no, skip
1010	movw	#0,INTIOBASE+MMUBASE+MMUCMD+2
1011	movw	#MMU_IEN+MMU_CEN+MMU_FPE,INTIOBASE+MMUBASE+MMUCMD+2
1012					| enable FPU and caches
1013	moveq	#0,d0			| ensure TT regs are disabled
1014	.long	0x4e7b0004		| movc d0,itt0
1015	.long	0x4e7b0005		| movc d0,itt1
1016	.long	0x4e7b0006		| movc d0,dtt0
1017	.long	0x4e7b0007		| movc d0,dtt1
1018	.word	0xf4d8			| cinva bc
1019	.word	0xf518			| pflusha
1020	movl	#0x8000,d0
1021	.long	0x4e7b0003		| movc d0,tc
1022	movl	#0x80008000,d0
1023	movc	d0,cacr			| turn on both caches
1024	jmp	Lenab1
1025Lmotommu2:
1026	movl	#MMU_IEN+MMU_FPE,INTIOBASE+MMUBASE+MMUCMD
1027					| enable 68881 and i-cache
1028	movl	#0x82c0aa00,a2@		| value to load TC with
1029	pmove	a2@,tc			| load it
1030	jmp	Lenab1
1031Lhpmmu3:
1032	movl	#0,INTIOBASE+MMUBASE+MMUCMD	| clear external cache
1033	movl	#MMU_ENAB,INTIOBASE+MMUBASE+MMUCMD | turn on MMU
1034	jmp	Lenab1				| jmp to mapped code
1035Lehighcode:
1036
1037/*
1038 * Should be running mapped from this point on
1039 */
1040Lenab1:
1041/* check for internal HP-IB in SYSFLAG */
1042	btst	#5,0xfffffed2		| internal HP-IB?
1043	jeq	Lfinish			| yes, have HP-IB just continue
1044	clrl	_internalhpib		| no, clear associated address
1045Lfinish:
1046/* select the software page size now */
1047	lea	tmpstk,sp		| temporary stack
1048	jbsr	_vm_set_page_size	| select software page size
1049/* set kernel stack, user SP, and initial pcb */
1050	lea	_kstack,a1		| proc0 kernel stack
1051	lea	a1@(UPAGES*NBPG-4),sp	| set kernel stack to end of area
1052	movl	#USRSTACK-4,a2
1053	movl	a2,usp			| init user SP
1054	movl	_proc0paddr,a1		| get proc0 pcb addr
1055	movl	a1,_curpcb		| proc0 is running
1056#ifdef FPCOPROC
1057	clrl	a1@(PCB_FPCTX)		| ensure null FP context
1058	movl	a1,sp@-
1059	jbsr	_m68881_restore		| restore it (does not kill a1)
1060	addql	#4,sp
1061#endif
1062/* flush TLB and turn on caches */
1063	jbsr	_TBIA			| invalidate TLB
1064	cmpl	#-2,_mmutype		| 68040?
1065	jeq	Lnocache0		| yes, cache already on
1066	movl	#CACHE_ON,d0
1067	movc	d0,cacr			| clear cache(s)
1068	tstl	_ectype
1069	jeq	Lnocache0
1070	MMUADDR(a0)
1071	orl	#MMU_CEN,a0@(MMUCMD)	| turn on external cache
1072Lnocache0:
1073/* final setup for C code */
1074	jbsr	_isrinit		| be ready for stray ints
1075	movw	#PSL_LOWIPL,sr		| lower SPL
1076	movl	d7,_boothowto		| save reboot flags
1077	movl	d6,_bootdev		|   and boot device
1078	jbsr	_main			| call main()
1079
1080/* proc[1] == init now running here;
1081 * create a null exception frame and return to user mode in icode
1082 */
1083	cmpl	#-2,_mmutype		| 68040?
1084	jne	Lnoflush		| no, skip
1085	.word	0xf478			| cpusha dc
1086	.word	0xf498			| cinva ic
1087Lnoflush:
1088	clrw	sp@-			| vector offset/frame type
1089	clrl	sp@-			| return to icode location 0
1090	movw	#PSL_USER,sp@-		| in user mode
1091	rte
1092
1093/*
1094 * Signal "trampoline" code (18 bytes).  Invoked from RTE setup by sendsig().
1095 *
1096 * Stack looks like:
1097 *
1098 *	sp+0 ->	signal number
1099 *	sp+4	signal specific code
1100 *	sp+8	pointer to signal context frame (scp)
1101 *	sp+12	address of handler
1102 *	sp+16	saved hardware state
1103 *			.
1104 *			.
1105 *	scp+0->	beginning of signal context frame
1106 */
1107	.globl	_sigcode, _esigcode, _sigcodetrap
1108	.data
1109_sigcode:
1110	movl	sp@(12),a0		| signal handler addr	(4 bytes)
1111	jsr	a0@			| call signal handler	(2 bytes)
1112	addql	#4,sp			| pop signo		(2 bytes)
1113_sigcodetrap:
1114	trap	#1			| special syscall entry	(2 bytes)
1115	movl	d0,sp@(4)		| save errno		(4 bytes)
1116	moveq	#1,d0			| syscall == exit	(2 bytes)
1117	trap	#0			| exit(errno)		(2 bytes)
1118	.align	2
1119_esigcode:
1120
1121/*
1122 * Icode is copied out to process 1 to exec init.
1123 * If the exec fails, process 1 exits.
1124 */
1125	.globl	_icode,_szicode
1126	.text
1127_icode:
1128	clrl	sp@-
1129	pea	pc@((argv-.)+2)
1130	pea	pc@((init-.)+2)
1131	clrl	sp@-
1132	moveq	#SYS_execve,d0
1133	trap	#0
1134	moveq	#SYS_exit,d0
1135	trap	#0
1136init:
1137	.asciz	"/sbin/init"
1138	.even
1139argv:
1140	.long	init+6-_icode		| argv[0] = "init" ("/sbin/init" + 6)
1141	.long	eicode-_icode		| argv[1] follows icode after copyout
1142	.long	0
1143eicode:
1144
1145_szicode:
1146	.long	_szicode-_icode
1147
1148/*
1149 * Primitives
1150 */
1151
1152#ifdef GPROF
1153#define	ENTRY(name) \
1154	.globl _/**/name; _/**/name: link a6,#0; jbsr mcount; unlk a6
1155#define ALTENTRY(name, rname) \
1156	ENTRY(name); jra rname+12
1157#else
1158#define	ENTRY(name) \
1159	.globl _/**/name; _/**/name:
1160#define ALTENTRY(name, rname) \
1161	.globl _/**/name; _/**/name:
1162#endif
1163
1164/*
1165 * For gcc2
1166 */
1167ENTRY(__main)
1168	rts
1169
1170/*
1171 * copyinstr(fromaddr, toaddr, maxlength, &lencopied)
1172 *
1173 * Copy a null terminated string from the user address space into
1174 * the kernel address space.
1175 * NOTE: maxlength must be < 64K
1176 */
1177ENTRY(copyinstr)
1178	movl	_curpcb,a0		| current pcb
1179	movl	#Lcisflt1,a0@(PCB_ONFAULT) | set up to catch faults
1180	movl	sp@(4),a0		| a0 = fromaddr
1181	movl	sp@(8),a1		| a1 = toaddr
1182	moveq	#0,d0
1183	movw	sp@(14),d0		| d0 = maxlength
1184	jlt	Lcisflt1		| negative count, error
1185	jeq	Lcisdone		| zero count, all done
1186	subql	#1,d0			| set up for dbeq
1187Lcisloop:
1188	movsb	a0@+,d1			| grab a byte
1189	nop
1190	movb	d1,a1@+			| copy it
1191	dbeq	d0,Lcisloop		| if !null and more, continue
1192	jne	Lcisflt2		| ran out of room, error
1193	moveq	#0,d0			| got a null, all done
1194Lcisdone:
1195	tstl	sp@(16)			| return length desired?
1196	jeq	Lcisret			| no, just return
1197	subl	sp@(4),a0		| determine how much was copied
1198	movl	sp@(16),a1		| return location
1199	movl	a0,a1@			| stash it
1200Lcisret:
1201	movl	_curpcb,a0		| current pcb
1202	clrl	a0@(PCB_ONFAULT) 	| clear fault addr
1203	rts
1204Lcisflt1:
1205	moveq	#EFAULT,d0		| copy fault
1206	jra	Lcisdone
1207Lcisflt2:
1208	moveq	#ENAMETOOLONG,d0	| ran out of space
1209	jra	Lcisdone
1210
1211/*
1212 * copyoutstr(fromaddr, toaddr, maxlength, &lencopied)
1213 *
1214 * Copy a null terminated string from the kernel
1215 * address space to the user address space.
1216 * NOTE: maxlength must be < 64K
1217 */
1218ENTRY(copyoutstr)
1219	movl	_curpcb,a0		| current pcb
1220	movl	#Lcosflt1,a0@(PCB_ONFAULT) | set up to catch faults
1221	movl	sp@(4),a0		| a0 = fromaddr
1222	movl	sp@(8),a1		| a1 = toaddr
1223	moveq	#0,d0
1224	movw	sp@(14),d0		| d0 = maxlength
1225	jlt	Lcosflt1		| negative count, error
1226	jeq	Lcosdone		| zero count, all done
1227	subql	#1,d0			| set up for dbeq
1228Lcosloop:
1229	movb	a0@+,d1			| grab a byte
1230	movsb	d1,a1@+			| copy it
1231	nop
1232	dbeq	d0,Lcosloop		| if !null and more, continue
1233	jne	Lcosflt2		| ran out of room, error
1234	moveq	#0,d0			| got a null, all done
1235Lcosdone:
1236	tstl	sp@(16)			| return length desired?
1237	jeq	Lcosret			| no, just return
1238	subl	sp@(4),a0		| determine how much was copied
1239	movl	sp@(16),a1		| return location
1240	movl	a0,a1@			| stash it
1241Lcosret:
1242	movl	_curpcb,a0		| current pcb
1243	clrl	a0@(PCB_ONFAULT) 	| clear fault addr
1244	rts
1245Lcosflt1:
1246	moveq	#EFAULT,d0		| copy fault
1247	jra	Lcosdone
1248Lcosflt2:
1249	moveq	#ENAMETOOLONG,d0	| ran out of space
1250	jra	Lcosdone
1251
1252/*
1253 * copystr(fromaddr, toaddr, maxlength, &lencopied)
1254 *
1255 * Copy a null terminated string from one point to another in
1256 * the kernel address space.
1257 * NOTE: maxlength must be < 64K
1258 */
1259ENTRY(copystr)
1260	movl	sp@(4),a0		| a0 = fromaddr
1261	movl	sp@(8),a1		| a1 = toaddr
1262	moveq	#0,d0
1263	movw	sp@(14),d0		| d0 = maxlength
1264	jlt	Lcsflt1			| negative count, error
1265	jeq	Lcsdone			| zero count, all done
1266	subql	#1,d0			| set up for dbeq
1267Lcsloop:
1268	movb	a0@+,a1@+		| copy a byte
1269	dbeq	d0,Lcsloop		| if !null and more, continue
1270	jne	Lcsflt2			| ran out of room, error
1271	moveq	#0,d0			| got a null, all done
1272Lcsdone:
1273	tstl	sp@(16)			| return length desired?
1274	jeq	Lcsret			| no, just return
1275	subl	sp@(4),a0		| determine how much was copied
1276	movl	sp@(16),a1		| return location
1277	movl	a0,a1@			| stash it
1278Lcsret:
1279	rts
1280Lcsflt1:
1281	moveq	#EFAULT,d0		| copy fault
1282	jra	Lcsdone
1283Lcsflt2:
1284	moveq	#ENAMETOOLONG,d0	| ran out of space
1285	jra	Lcsdone
1286
1287/*
1288 * Copyin(from_user, to_kernel, len)
1289 * Copyout(from_kernel, to_user, len)
1290 *
1291 * Copy specified amount of data between kernel and user space.
1292 *
1293 * XXX both use the DBcc instruction which has 16-bit limitation so only
1294 * 64k units can be copied, where "unit" is either a byte or a longword
1295 * depending on alignment.  To be safe, assume it can copy at most
1296 * 64k bytes.  Don't make MAXBSIZE or MAXPHYS larger than 64k without
1297 * fixing this code!
1298 */
1299ENTRY(copyin)
1300	movl	d2,sp@-			| scratch register
1301	movl	_curpcb,a0		| current pcb
1302	movl	#Lciflt,a0@(PCB_ONFAULT) | set up to catch faults
1303	movl	sp@(16),d2		| check count
1304	jlt	Lciflt			| negative, error
1305	jeq	Lcidone			| zero, done
1306	movl	sp@(8),a0		| src address
1307	movl	sp@(12),a1		| dest address
1308	movl	a0,d0
1309	btst	#0,d0			| src address odd?
1310	jeq	Lcieven			| no, go check dest
1311	movsb	a0@+,d1			| yes, get a byte
1312	nop
1313	movb	d1,a1@+			| put a byte
1314	subql	#1,d2			| adjust count
1315	jeq	Lcidone			| exit if done
1316Lcieven:
1317	movl	a1,d0
1318	btst	#0,d0			| dest address odd?
1319	jne	Lcibyte			| yes, must copy by bytes
1320	movl	d2,d0			| no, get count
1321	lsrl	#2,d0			| convert to longwords
1322	jeq	Lcibyte			| no longwords, copy bytes
1323	subql	#1,d0			| set up for dbf
1324Lcilloop:
1325	movsl	a0@+,d1			| get a long
1326	nop
1327	movl	d1,a1@+			| put a long
1328	dbf	d0,Lcilloop		| til done
1329	andl	#3,d2			| what remains
1330	jeq	Lcidone			| all done
1331Lcibyte:
1332	subql	#1,d2			| set up for dbf
1333Lcibloop:
1334	movsb	a0@+,d1			| get a byte
1335	nop
1336	movb	d1,a1@+			| put a byte
1337	dbf	d2,Lcibloop		| til done
1338Lcidone:
1339	moveq	#0,d0			| success
1340Lciexit:
1341	movl	_curpcb,a0		| current pcb
1342	clrl	a0@(PCB_ONFAULT) 	| clear fault catcher
1343	movl	sp@+,d2			| restore scratch reg
1344	rts
1345Lciflt:
1346	moveq	#EFAULT,d0		| got a fault
1347	jra	Lciexit
1348
1349ENTRY(copyout)
1350	movl	d2,sp@-			| scratch register
1351	movl	_curpcb,a0		| current pcb
1352	movl	#Lcoflt,a0@(PCB_ONFAULT) | catch faults
1353	movl	sp@(16),d2		| check count
1354	jlt	Lcoflt			| negative, error
1355	jeq	Lcodone			| zero, done
1356	movl	sp@(8),a0		| src address
1357	movl	sp@(12),a1		| dest address
1358	movl	a0,d0
1359	btst	#0,d0			| src address odd?
1360	jeq	Lcoeven			| no, go check dest
1361	movb	a0@+,d1			| yes, get a byte
1362	movsb	d1,a1@+			| put a byte
1363	nop
1364	subql	#1,d2			| adjust count
1365	jeq	Lcodone			| exit if done
1366Lcoeven:
1367	movl	a1,d0
1368	btst	#0,d0			| dest address odd?
1369	jne	Lcobyte			| yes, must copy by bytes
1370	movl	d2,d0			| no, get count
1371	lsrl	#2,d0			| convert to longwords
1372	jeq	Lcobyte			| no longwords, copy bytes
1373	subql	#1,d0			| set up for dbf
1374Lcolloop:
1375	movl	a0@+,d1			| get a long
1376	movsl	d1,a1@+			| put a long
1377	nop
1378	dbf	d0,Lcolloop		| til done
1379	andl	#3,d2			| what remains
1380	jeq	Lcodone			| all done
1381Lcobyte:
1382	subql	#1,d2			| set up for dbf
1383Lcobloop:
1384	movb	a0@+,d1			| get a byte
1385	movsb	d1,a1@+			| put a byte
1386	nop
1387	dbf	d2,Lcobloop		| til done
1388Lcodone:
1389	moveq	#0,d0			| success
1390Lcoexit:
1391	movl	_curpcb,a0		| current pcb
1392	clrl	a0@(PCB_ONFAULT) 	| clear fault catcher
1393	movl	sp@+,d2			| restore scratch reg
1394	rts
1395Lcoflt:
1396	moveq	#EFAULT,d0		| got a fault
1397	jra	Lcoexit
1398
1399/*
1400 * non-local gotos
1401 */
1402ENTRY(setjmp)
1403	movl	sp@(4),a0	| savearea pointer
1404	moveml	#0xFCFC,a0@	| save d2-d7/a2-a7
1405	movl	sp@,a0@(48)	| and return address
1406	moveq	#0,d0		| return 0
1407	rts
1408
1409ENTRY(longjmp)
1410	movl	sp@(4),a0
1411	moveml	a0@+,#0xFCFC
1412	movl	a0@,sp@
1413	moveq	#1,d0
1414	rts
1415
1416/*
1417 * The following primitives manipulate the run queues.
1418 * _whichqs tells which of the 32 queues _qs
1419 * have processes in them.  Setrq puts processes into queues, Remrq
1420 * removes them from queues.  The running process is on no queue,
1421 * other processes are on a queue related to p->p_pri, divided by 4
1422 * actually to shrink the 0-127 range of priorities into the 32 available
1423 * queues.
1424 */
1425
1426	.globl	_whichqs,_qs,_cnt,_panic
1427	.globl	_curproc,_want_resched
1428
1429/*
1430 * Setrq(p)
1431 *
1432 * Call should be made at spl6(), and p->p_stat should be SRUN
1433 */
1434ENTRY(setrq)
1435	movl	sp@(4),a0
1436	tstl	a0@(P_RLINK)
1437	jeq	Lset1
1438	movl	#Lset2,sp@-
1439	jbsr	_panic
1440Lset1:
1441	clrl	d0
1442	movb	a0@(P_PRI),d0
1443	lsrb	#2,d0
1444	movl	_whichqs,d1
1445	bset	d0,d1
1446	movl	d1,_whichqs
1447	lslb	#3,d0
1448	addl	#_qs,d0
1449	movl	d0,a0@(P_LINK)
1450	movl	d0,a1
1451	movl	a1@(P_RLINK),a0@(P_RLINK)
1452	movl	a0,a1@(P_RLINK)
1453	movl	a0@(P_RLINK),a1
1454	movl	a0,a1@(P_LINK)
1455	rts
1456
1457Lset2:
1458	.asciz	"setrq"
1459	.even
1460
1461/*
1462 * Remrq(p)
1463 *
1464 * Call should be made at spl6().
1465 */
1466ENTRY(remrq)
1467	movl	sp@(4),a0
1468	clrl	d0
1469	movb	a0@(P_PRI),d0
1470	lsrb	#2,d0
1471	movl	_whichqs,d1
1472	bclr	d0,d1
1473	jne	Lrem1
1474	movl	#Lrem3,sp@-
1475	jbsr	_panic
1476Lrem1:
1477	movl	d1,_whichqs
1478	movl	a0@(P_LINK),a1
1479	movl	a0@(P_RLINK),a1@(P_RLINK)
1480	movl	a0@(P_RLINK),a1
1481	movl	a0@(P_LINK),a1@(P_LINK)
1482	movl	#_qs,a1
1483	movl	d0,d1
1484	lslb	#3,d1
1485	addl	d1,a1
1486	cmpl	a1@(P_LINK),a1
1487	jeq	Lrem2
1488	movl	_whichqs,d1
1489	bset	d0,d1
1490	movl	d1,_whichqs
1491Lrem2:
1492	clrl	a0@(P_RLINK)
1493	rts
1494
1495Lrem3:
1496	.asciz	"remrq"
1497Lsw0:
1498	.asciz	"swtch"
1499	.even
1500
1501	.globl	_curpcb
1502	.globl	_masterpaddr	| XXX compatibility (debuggers)
1503	.data
1504_masterpaddr:			| XXX compatibility (debuggers)
1505_curpcb:
1506	.long	0
1507mdpflag:
1508	.byte	0		| copy of proc md_flags low byte
1509	.align	2
1510	.comm	nullpcb,SIZEOF_PCB
1511	.text
1512
1513/*
1514 * At exit of a process, do a swtch for the last time.
1515 * The mapping of the pcb at p->p_addr has already been deleted,
1516 * and the memory for the pcb+stack has been freed.
1517 * The ipl is high enough to prevent the memory from being reallocated.
1518 */
1519ENTRY(swtch_exit)
1520	movl	#nullpcb,_curpcb	| save state into garbage pcb
1521	lea	tmpstk,sp		| goto a tmp stack
1522	jra	_cpu_swtch
1523
1524/*
1525 * When no processes are on the runq, Swtch branches to idle
1526 * to wait for something to come ready.
1527 */
1528	.globl	idle
1529Lidle:
1530	stop	#PSL_LOWIPL
1531idle:
1532	movw	#PSL_HIGHIPL,sr
1533	tstl	_whichqs
1534	jeq	Lidle
1535	movw	#PSL_LOWIPL,sr
1536	jra	Lsw1
1537
1538Lbadsw:
1539	movl	#Lsw0,sp@-
1540	jbsr	_panic
1541	/*NOTREACHED*/
1542
1543/*
1544 * cpu_swtch()
1545 *
1546 * NOTE: On the mc68851 (318/319/330) we attempt to avoid flushing the
1547 * entire ATC.  The effort involved in selective flushing may not be
1548 * worth it, maybe we should just flush the whole thing?
1549 *
1550 * NOTE 2: With the new VM layout we now no longer know if an inactive
1551 * user's PTEs have been changed (formerly denoted by the SPTECHG p_flag
1552 * bit).  For now, we just always flush the full ATC.
1553 */
1554ENTRY(cpu_swtch)
1555	movl	_curpcb,a0		| current pcb
1556	movw	sr,a0@(PCB_PS)		| save sr before changing ipl
1557#ifdef notyet
1558	movl	_curproc,sp@-		| remember last proc running
1559#endif
1560	clrl	_curproc
1561	addql	#1,_cnt+V_SWTCH
1562
1563Lsw1:
1564	/*
1565	 * Find the highest-priority queue that isn't empty,
1566	 * then take the first proc from that queue.
1567	 */
1568	clrl	d0
1569	lea	_whichqs,a0
1570	movl	a0@,d1
1571Lswchk:
1572	btst	d0,d1
1573	jne	Lswfnd
1574	addqb	#1,d0
1575	cmpb	#32,d0
1576	jne	Lswchk
1577	jra	idle
1578Lswfnd:
1579	movw	#PSL_HIGHIPL,sr		| lock out interrupts
1580	movl	a0@,d1			| and check again...
1581	bclr	d0,d1
1582	jeq	Lsw1			| proc moved, rescan
1583	movl	d1,a0@			| update whichqs
1584	moveq	#1,d1			| double check for higher priority
1585	lsll	d0,d1			| process (which may have snuck in
1586	subql	#1,d1			| while we were finding this one)
1587	andl	a0@,d1
1588	jeq	Lswok			| no one got in, continue
1589	movl	a0@,d1
1590	bset	d0,d1			| otherwise put this one back
1591	movl	d1,a0@
1592	jra	Lsw1			| and rescan
1593Lswok:
1594	movl	d0,d1
1595	lslb	#3,d1			| convert queue number to index
1596	addl	#_qs,d1			| locate queue (q)
1597	movl	d1,a1
1598	cmpl	a1@(P_LINK),a1		| anyone on queue?
1599	jeq	Lbadsw			| no, panic
1600	movl	a1@(P_LINK),a0			| p = q->p_link
1601	movl	a0@(P_LINK),a1@(P_LINK)		| q->p_link = p->p_link
1602	movl	a0@(P_LINK),a1			| q = p->p_link
1603	movl	a0@(P_RLINK),a1@(P_RLINK)	| q->p_rlink = p->p_rlink
1604	cmpl	a0@(P_LINK),d1		| anyone left on queue?
1605	jeq	Lsw2			| no, skip
1606	movl	_whichqs,d1
1607	bset	d0,d1			| yes, reset bit
1608	movl	d1,_whichqs
1609Lsw2:
1610	movl	a0,_curproc
1611	clrl	_want_resched
1612#ifdef notyet
1613	movl	sp@+,a1
1614	cmpl	a0,a1			| switching to same proc?
1615	jeq	Lswdone			| yes, skip save and restore
1616#endif
1617	/*
1618	 * Save state of previous process in its pcb.
1619	 */
1620	movl	_curpcb,a1
1621	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1622	movl	usp,a2			| grab USP (a2 has been saved)
1623	movl	a2,a1@(PCB_USP)		| and save it
1624#ifdef FPCOPROC
1625	lea	a1@(PCB_FPCTX),a2	| pointer to FP save area
1626	fsave	a2@			| save FP state
1627	tstb	a2@			| null state frame?
1628	jeq	Lswnofpsave		| yes, all done
1629	fmovem	fp0-fp7,a2@(216)	| save FP general registers
1630	fmovem	fpcr/fpsr/fpi,a2@(312)	| save FP control registers
1631Lswnofpsave:
1632#endif
1633
1634#ifdef DIAGNOSTIC
1635	tstl	a0@(P_WCHAN)
1636	jne	Lbadsw
1637	cmpb	#SRUN,a0@(P_STAT)
1638	jne	Lbadsw
1639#endif
1640	clrl	a0@(P_RLINK)		| clear back link
1641	movb	a0@(P_MDFLAG+3),mdpflag	| low byte of p_md.md_flags
1642	movl	a0@(P_ADDR),a1		| get p_addr
1643	movl	a1,_curpcb
1644
1645	/* see if pmap_activate needs to be called; should remove this */
1646	movl	a0@(P_VMSPACE),a0	| vmspace = p->p_vmspace
1647#ifdef DIAGNOSTIC
1648	tstl	a0			| map == VM_MAP_NULL?
1649	jeq	Lbadsw			| panic
1650#endif
1651	lea	a0@(VM_PMAP),a0		| pmap = &vmspace.vm_pmap
1652	tstl	a0@(PM_STCHG)		| pmap->st_changed?
1653	jeq	Lswnochg		| no, skip
1654	pea	a1@			| push pcb (at p_addr)
1655	pea	a0@			| push pmap
1656	jbsr	_pmap_activate		| pmap_activate(pmap, pcb)
1657	addql	#8,sp
1658	movl	_curpcb,a1		| restore p_addr
1659Lswnochg:
1660
1661	movl	#PGSHIFT,d1
1662	movl	a1,d0
1663	lsrl	d1,d0			| convert p_addr to page number
1664	lsll	#2,d0			| and now to Sysmap offset
1665	addl	_Sysmap,d0		| add Sysmap base to get PTE addr
1666#ifdef notdef
1667	movw	#PSL_HIGHIPL,sr		| go crit while changing PTEs
1668#endif
1669	lea	tmpstk,sp		| now goto a tmp stack for NMI
1670	movl	d0,a0			| address of new context
1671	movl	_Umap,a2		| address of PTEs for kstack
1672	moveq	#UPAGES-1,d0		| sizeof kstack
1673Lres1:
1674	movl	a0@+,d1			| get PTE
1675	andl	#~PG_PROT,d1		| mask out old protection
1676	orl	#PG_RW+PG_V,d1		| ensure valid and writable
1677	movl	d1,a2@+			| load it up
1678	dbf	d0,Lres1		| til done
1679#if defined(HP380)
1680	cmpl	#-2,_mmutype		| 68040?
1681	jne	Lres1a			| no, skip
1682	.word	0xf518			| yes, pflusha
1683	movl	a1@(PCB_USTP),d0	| get USTP
1684	moveq	#PGSHIFT,d1
1685	lsll	d1,d0			| convert to addr
1686	.long	0x4e7b0806		| movc d0,urp
1687	jra	Lcxswdone
1688Lres1a:
1689#endif
1690	movl	#CACHE_CLR,d0
1691	movc	d0,cacr			| invalidate cache(s)
1692#if defined(HP330) || defined(HP360) || defined(HP370)
1693	tstl	_mmutype		| HP MMU?
1694	jeq	Lhpmmu4			| yes, skip
1695	pflusha				| flush entire TLB
1696	movl	a1@(PCB_USTP),d0	| get USTP
1697	moveq	#PGSHIFT,d1
1698	lsll	d1,d0			| convert to addr
1699	lea	_protorp,a0		| CRP prototype
1700	movl	d0,a0@(4)		| stash USTP
1701	pmove	a0@,crp			| load new user root pointer
1702	jra	Lcxswdone		| thats it
1703Lhpmmu4:
1704#endif
1705#if defined(HP320) || defined(HP350)
1706	MMUADDR(a0)
1707	movl	a0@(MMUTBINVAL),d1	| invalidate TLB
1708	tstl	_ectype			| got external VAC?
1709	jle	Lnocache1		| no, skip
1710	andl	#~MMU_CEN,a0@(MMUCMD)	| toggle cache enable
1711	orl	#MMU_CEN,a0@(MMUCMD)	| to clear data cache
1712Lnocache1:
1713	movl	a1@(PCB_USTP),a0@(MMUUSTP) | context switch
1714#endif
1715Lcxswdone:
1716	moveml	a1@(PCB_REGS),#0xFCFC	| and registers
1717	movl	a1@(PCB_USP),a0
1718	movl	a0,usp			| and USP
1719#ifdef FPCOPROC
1720	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1721	tstb	a0@			| null state frame?
1722	jeq	Lresfprest		| yes, easy
1723#if defined(HP380)
1724	cmpl	#-2,_mmutype		| 68040?
1725	jne	Lresnot040		| no, skip
1726	clrl	sp@-			| yes...
1727	frestore sp@+			| ...magic!
1728Lresnot040:
1729#endif
1730	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
1731	fmovem	a0@(216),fp0-fp7	| restore FP general registers
1732Lresfprest:
1733	frestore a0@			| restore state
1734#endif
1735	movw	a1@(PCB_PS),sr		| no, restore PS
1736	moveq	#1,d0			| return 1 (for alternate returns)
1737	rts
1738
1739/*
1740 * savectx(pcb, altreturn)
1741 * Update pcb, saving current processor state and arranging
1742 * for alternate return ala longjmp in swtch if altreturn is true.
1743 */
1744ENTRY(savectx)
1745	movl	sp@(4),a1
1746	movw	sr,a1@(PCB_PS)
1747	movl	usp,a0			| grab USP
1748	movl	a0,a1@(PCB_USP)		| and save it
1749	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1750#ifdef FPCOPROC
1751	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1752	fsave	a0@			| save FP state
1753	tstb	a0@			| null state frame?
1754	jeq	Lsvnofpsave		| yes, all done
1755	fmovem	fp0-fp7,a0@(216)	| save FP general registers
1756	fmovem	fpcr/fpsr/fpi,a0@(312)	| save FP control registers
1757Lsvnofpsave:
1758#endif
1759	tstl	sp@(8)			| altreturn?
1760	jeq	Lsavedone
1761	movl	sp,d0			| relocate current sp relative to a1
1762	subl	#_kstack,d0		|   (sp is relative to kstack):
1763	addl	d0,a1			|   a1 += sp - kstack;
1764	movl	sp@,a1@			| write return pc at (relocated) sp@
1765Lsavedone:
1766	moveq	#0,d0			| return 0
1767	rts
1768
1769/*
1770 * {fu,su},{byte,sword,word}
1771 */
1772ALTENTRY(fuiword, _fuword)
1773ENTRY(fuword)
1774	movl	sp@(4),a0		| address to read
1775	movl	_curpcb,a1		| current pcb
1776	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1777	movsl	a0@,d0			| do read from user space
1778	nop
1779	jra	Lfsdone
1780
1781ENTRY(fusword)
1782	movl	sp@(4),a0
1783	movl	_curpcb,a1		| current pcb
1784	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1785	moveq	#0,d0
1786	movsw	a0@,d0			| do read from user space
1787	nop
1788	jra	Lfsdone
1789
1790/* Just like fusword, but tells trap code not to page in. */
1791ENTRY(fuswintr)
1792	movl	sp@(4),a0
1793	movl	_curpcb,a1
1794	movl	#_fswintr,a1@(PCB_ONFAULT)
1795	moveq	#0,d0
1796	movsw	a0@,d0
1797	nop
1798	jra	Lfsdone
1799
1800ALTENTRY(fuibyte, _fubyte)
1801ENTRY(fubyte)
1802	movl	sp@(4),a0		| address to read
1803	movl	_curpcb,a1		| current pcb
1804	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1805	moveq	#0,d0
1806	movsb	a0@,d0			| do read from user space
1807	nop
1808	jra	Lfsdone
1809
1810Lfserr:
1811	moveq	#-1,d0			| error indicator
1812Lfsdone:
1813	clrl	a1@(PCB_ONFAULT) 	| clear fault address
1814	rts
1815
1816/* Just like Lfserr, but the address is different (& exported). */
1817	.globl	_fswintr
1818_fswintr:
1819	moveq	#-1,d0
1820	jra	Lfsdone
1821
1822
1823/*
1824 * Write a longword in user instruction space.
1825 * Largely the same as suword but with a final i-cache purge on those
1826 * machines with split caches.
1827 */
1828ENTRY(suiword)
1829	movl	sp@(4),a0		| address to write
1830	movl	sp@(8),d0		| value to put there
1831	movl	_curpcb,a1		| current pcb
1832	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1833	movsl	d0,a0@			| do write to user space
1834	nop
1835	moveq	#0,d0			| indicate no fault
1836#if defined(HP380)
1837	cmpl	#-2,_mmutype		| 68040?
1838	jne	Lsuicpurge		| no, skip
1839	.word	0xf498			| cinva ic (XXX overkill)
1840	jra	Lfsdone
1841Lsuicpurge:
1842#endif
1843	movl	#IC_CLEAR,d1
1844	movc	d1,cacr			| invalidate i-cache
1845	jra	Lfsdone
1846
1847ENTRY(suword)
1848	movl	sp@(4),a0		| address to write
1849	movl	sp@(8),d0		| value to put there
1850	movl	_curpcb,a1		| current pcb
1851	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1852	movsl	d0,a0@			| do write to user space
1853	nop
1854	moveq	#0,d0			| indicate no fault
1855	jra	Lfsdone
1856
1857ENTRY(susword)
1858	movl	sp@(4),a0		| address to write
1859	movw	sp@(10),d0		| value to put there
1860	movl	_curpcb,a1		| current pcb
1861	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1862	movsw	d0,a0@			| do write to user space
1863	nop
1864	moveq	#0,d0			| indicate no fault
1865	jra	Lfsdone
1866
1867ENTRY(suswintr)
1868	movl	sp@(4),a0
1869	movw	sp@(10),d0
1870	movl	_curpcb,a1
1871	movl	#_fswintr,a1@(PCB_ONFAULT)
1872	movsw	d0,a0@
1873	nop
1874	moveq	#0,d0
1875	jra	Lfsdone
1876
1877ALTENTRY(suibyte, _subyte)
1878ENTRY(subyte)
1879	movl	sp@(4),a0		| address to write
1880	movb	sp@(11),d0		| value to put there
1881	movl	_curpcb,a1		| current pcb
1882	movl	#Lfserr,a1@(PCB_ONFAULT) | where to return to on a fault
1883	movsb	d0,a0@			| do write to user space
1884	nop
1885	moveq	#0,d0			| indicate no fault
1886	jra	Lfsdone
1887
1888#if defined(HP380)
1889ENTRY(suline)
1890	movl	sp@(4),a0		| address to write
1891	movl	_curpcb,a1		| current pcb
1892	movl	#Lslerr,a1@(PCB_ONFAULT) | where to return to on a fault
1893	movl	sp@(8),a1		| address of line
1894	movl	a1@+,d0			| get lword
1895	movsl	d0,a0@+			| put lword
1896	nop				| sync
1897	movl	a1@+,d0			| get lword
1898	movsl	d0,a0@+			| put lword
1899	nop				| sync
1900	movl	a1@+,d0			| get lword
1901	movsl	d0,a0@+			| put lword
1902	nop				| sync
1903	movl	a1@+,d0			| get lword
1904	movsl	d0,a0@+			| put lword
1905	nop				| sync
1906	moveq	#0,d0			| indicate no fault
1907	jra	Lsldone
1908Lslerr:
1909	moveq	#-1,d0
1910Lsldone:
1911	movl	_curpcb,a1		| current pcb
1912	clrl	a1@(PCB_ONFAULT) 	| clear fault address
1913	rts
1914#endif
1915
1916/*
1917 * Invalidate entire TLB.
1918 */
1919ENTRY(TBIA)
1920__TBIA:
1921#if defined(HP380)
1922	cmpl	#-2,_mmutype		| 68040?
1923	jne	Lmotommu3		| no, skip
1924	.word	0xf518			| yes, pflusha
1925	rts
1926Lmotommu3:
1927#endif
1928#if defined(HP330) || defined(HP360) || defined(HP370)
1929	tstl	_mmutype		| HP MMU?
1930	jeq	Lhpmmu6			| yes, skip
1931	pflusha				| flush entire TLB
1932#if defined(HP360) || defined(HP370)
1933	jpl	Lmc68851a		| 68851 implies no d-cache
1934	movl	#DC_CLEAR,d0
1935	movc	d0,cacr			| invalidate on-chip d-cache
1936Lmc68851a:
1937#endif
1938	rts
1939Lhpmmu6:
1940#endif
1941#if defined(HP320) || defined(HP350)
1942	MMUADDR(a0)
1943	movl	a0@(MMUTBINVAL),sp@-	| do not ask me, this
1944	addql	#4,sp			|   is how hpux does it
1945#ifdef DEBUG
1946	tstl	fullcflush
1947	jne	__DCIA			| XXX: invalidate entire cache
1948#endif
1949#endif
1950	rts
1951
1952/*
1953 * Invalidate any TLB entry for given VA (TB Invalidate Single)
1954 */
1955ENTRY(TBIS)
1956#ifdef DEBUG
1957	tstl	fulltflush		| being conservative?
1958	jne	__TBIA			| yes, flush entire TLB
1959#endif
1960#if defined(HP380)
1961	cmpl	#-2,_mmutype		| 68040?
1962	jne	Lmotommu4		| no, skip
1963	movl	sp@(4),a0
1964	movc	dfc,d1
1965	moveq	#1,d0			| user space
1966	movc	d0,dfc
1967	.word	0xf508			| pflush a0@
1968	moveq	#5,d0			| super space
1969	movc	d0,dfc
1970	.word	0xf508			| pflush a0@
1971	movc	d1,dfc
1972	rts
1973Lmotommu4:
1974#endif
1975#if defined(HP330) || defined(HP360) || defined(HP370)
1976	tstl	_mmutype		| HP MMU?
1977	jeq	Lhpmmu5			| yes, skip
1978	movl	sp@(4),a0		| get addr to flush
1979#if defined(HP360) || defined(HP370)
1980	jpl	Lmc68851b		| is 68851?
1981	pflush	#0,#0,a0@		| flush address from both sides
1982	movl	#DC_CLEAR,d0
1983	movc	d0,cacr			| invalidate on-chip data cache
1984	rts
1985Lmc68851b:
1986#endif
1987	pflushs	#0,#0,a0@		| flush address from both sides
1988	rts
1989Lhpmmu5:
1990#endif
1991#if defined(HP320) || defined(HP350)
1992	movl	sp@(4),d0		| VA to invalidate
1993	bclr	#0,d0			| ensure even
1994	movl	d0,a0
1995	movw	sr,d1			| go critical
1996	movw	#PSL_HIGHIPL,sr		|   while in purge space
1997	moveq	#FC_PURGE,d0		| change address space
1998	movc	d0,dfc			|   for destination
1999	moveq	#0,d0			| zero to invalidate?
2000	movsl	d0,a0@			| hit it
2001	moveq	#FC_USERD,d0		| back to old
2002	movc	d0,dfc			|   address space
2003	movw	d1,sr			| restore IPL
2004#endif
2005	rts
2006
2007/*
2008 * Invalidate supervisor side of TLB
2009 */
2010ENTRY(TBIAS)
2011#ifdef DEBUG
2012	tstl	fulltflush		| being conservative?
2013	jne	__TBIA			| yes, flush everything
2014#endif
2015#if defined(HP380)
2016	cmpl	#-2,_mmutype		| 68040?
2017	jne	Lmotommu5		| no, skip
2018	.word	0xf518			| yes, pflusha (for now) XXX
2019	rts
2020Lmotommu5:
2021#endif
2022#if defined(HP330) || defined(HP360) || defined(HP370)
2023	tstl	_mmutype		| HP MMU?
2024	jeq	Lhpmmu7			| yes, skip
2025#if defined(HP360) || defined(HP370)
2026	jpl	Lmc68851c		| 68851?
2027	pflush #4,#4			| flush supervisor TLB entries
2028	movl	#DC_CLEAR,d0
2029	movc	d0,cacr			| invalidate on-chip d-cache
2030	rts
2031Lmc68851c:
2032#endif
2033	pflushs #4,#4			| flush supervisor TLB entries
2034	rts
2035Lhpmmu7:
2036#endif
2037#if defined(HP320) || defined(HP350)
2038	MMUADDR(a0)
2039	movl	#0x8000,d0		| more
2040	movl	d0,a0@(MMUTBINVAL)	|   HP magic
2041#ifdef DEBUG
2042	tstl	fullcflush
2043	jne	__DCIS			| XXX: invalidate entire sup. cache
2044#endif
2045#endif
2046	rts
2047
2048/*
2049 * Invalidate user side of TLB
2050 */
2051ENTRY(TBIAU)
2052#ifdef DEBUG
2053	tstl	fulltflush		| being conservative?
2054	jne	__TBIA			| yes, flush everything
2055#endif
2056#if defined(HP380)
2057	cmpl	#-2,_mmutype		| 68040?
2058	jne	Lmotommu6		| no, skip
2059	.word	0xf518			| yes, pflusha (for now) XXX
2060	rts
2061Lmotommu6:
2062#endif
2063#if defined(HP330) || defined(HP360) || defined(HP370)
2064	tstl	_mmutype		| HP MMU?
2065	jeq	Lhpmmu8			| yes, skip
2066#if defined(HP360) || defined(HP370)
2067	jpl	Lmc68851d		| 68851?
2068	pflush	#0,#4			| flush user TLB entries
2069	movl	#DC_CLEAR,d0
2070	movc	d0,cacr			| invalidate on-chip d-cache
2071	rts
2072Lmc68851d:
2073#endif
2074	pflushs	#0,#4			| flush user TLB entries
2075	rts
2076Lhpmmu8:
2077#endif
2078#if defined(HP320) || defined(HP350)
2079	MMUADDR(a0)
2080	moveq	#0,d0			| more
2081	movl	d0,a0@(MMUTBINVAL)	|   HP magic
2082#ifdef DEBUG
2083	tstl	fullcflush
2084	jne	__DCIU			| XXX: invalidate entire user cache
2085#endif
2086#endif
2087	rts
2088
2089/*
2090 * Invalidate instruction cache
2091 */
2092ENTRY(ICIA)
2093#if defined(HP380)
2094ENTRY(ICPA)
2095	cmpl	#-2,_mmutype		| 68040
2096	jne	Lmotommu7		| no, skip
2097	.word	0xf498			| cinva ic
2098	rts
2099Lmotommu7:
2100#endif
2101	movl	#IC_CLEAR,d0
2102	movc	d0,cacr			| invalidate i-cache
2103	rts
2104
2105/*
2106 * Invalidate data cache.
2107 * HP external cache allows for invalidation of user/supervisor portions.
2108 * NOTE: we do not flush 68030 on-chip cache as there are no aliasing
2109 * problems with DC_WA.  The only cases we have to worry about are context
2110 * switch and TLB changes, both of which are handled "in-line" in resume
2111 * and TBI*.
2112 */
2113ENTRY(DCIA)
2114__DCIA:
2115#if defined(HP380)
2116	cmpl	#-2,_mmutype		| 68040
2117	jne	Lmotommu8		| no, skip
2118	/* XXX implement */
2119	rts
2120Lmotommu8:
2121#endif
2122#if defined(HP320) || defined(HP350)
2123	tstl	_ectype			| got external VAC?
2124	jle	Lnocache2		| no, all done
2125	MMUADDR(a0)
2126	andl	#~MMU_CEN,a0@(MMUCMD)	| disable cache in MMU control reg
2127	orl	#MMU_CEN,a0@(MMUCMD)	| reenable cache in MMU control reg
2128Lnocache2:
2129#endif
2130	rts
2131
2132ENTRY(DCIS)
2133__DCIS:
2134#if defined(HP380)
2135	cmpl	#-2,_mmutype		| 68040
2136	jne	Lmotommu9		| no, skip
2137	/* XXX implement */
2138	rts
2139Lmotommu9:
2140#endif
2141#if defined(HP320) || defined(HP350)
2142	tstl	_ectype			| got external VAC?
2143	jle	Lnocache3		| no, all done
2144	MMUADDR(a0)
2145	movl	a0@(MMUSSTP),d0		| read the supervisor STP
2146	movl	d0,a0@(MMUSSTP)		| write it back
2147Lnocache3:
2148#endif
2149	rts
2150
2151ENTRY(DCIU)
2152__DCIU:
2153#if defined(HP380)
2154	cmpl	#-2,_mmutype		| 68040
2155	jne	LmotommuA		| no, skip
2156	/* XXX implement */
2157	rts
2158LmotommuA:
2159#endif
2160#if defined(HP320) || defined(HP350)
2161	tstl	_ectype			| got external VAC?
2162	jle	Lnocache4		| no, all done
2163	MMUADDR(a0)
2164	movl	a0@(MMUUSTP),d0		| read the user STP
2165	movl	d0,a0@(MMUUSTP)		| write it back
2166Lnocache4:
2167#endif
2168	rts
2169
2170#if defined(HP380)
2171ENTRY(ICPL)
2172	movl	sp@(4),a0		| address
2173	.word	0xf488			| cinvl ic,a0@
2174	rts
2175ENTRY(ICPP)
2176	movl	sp@(4),a0		| address
2177	.word	0xf490			| cinvp ic,a0@
2178	rts
2179ENTRY(DCPL)
2180	movl	sp@(4),a0		| address
2181	.word	0xf448			| cinvl dc,a0@
2182	rts
2183ENTRY(DCPP)
2184	movl	sp@(4),a0		| address
2185	.word	0xf450			| cinvp dc,a0@
2186	rts
2187ENTRY(DCPA)
2188	.word	0xf458			| cinva dc
2189	rts
2190ENTRY(DCFL)
2191	movl	sp@(4),a0		| address
2192	.word	0xf468			| cpushl dc,a0@
2193	rts
2194ENTRY(DCFP)
2195	movl	sp@(4),a0		| address
2196	.word	0xf470			| cpushp dc,a0@
2197	rts
2198#endif
2199
2200ENTRY(PCIA)
2201#if defined(HP380)
2202ENTRY(DCFA)
2203	cmpl	#-2,_mmutype		| 68040
2204	jne	LmotommuB		| no, skip
2205	.word	0xf478			| cpusha dc
2206	rts
2207LmotommuB:
2208#endif
2209#if defined(HP360) || defined(HP370)
2210	movl	#DC_CLEAR,d0
2211	movc	d0,cacr			| invalidate on-chip d-cache
2212	tstl	_ectype			| got external PAC?
2213	jge	Lnocache6		| no, all done
2214	MMUADDR(a0)
2215	andl	#~MMU_CEN,a0@(MMUCMD)	| disable cache in MMU control reg
2216	orl	#MMU_CEN,a0@(MMUCMD)	| reenable cache in MMU control reg
2217Lnocache6:
2218#endif
2219	rts
2220
2221ENTRY(ecacheon)
2222	tstl	_ectype
2223	jeq	Lnocache7
2224	MMUADDR(a0)
2225	orl	#MMU_CEN,a0@(MMUCMD)
2226Lnocache7:
2227	rts
2228
2229ENTRY(ecacheoff)
2230	tstl	_ectype
2231	jeq	Lnocache8
2232	MMUADDR(a0)
2233	andl	#~MMU_CEN,a0@(MMUCMD)
2234Lnocache8:
2235	rts
2236
2237/*
2238 * Get callers current SP value.
2239 * Note that simply taking the address of a local variable in a C function
2240 * doesn't work because callee saved registers may be outside the stack frame
2241 * defined by A6 (e.g. GCC generated code).
2242 */
2243	.globl	_getsp
2244_getsp:
2245	movl	sp,d0			| get current SP
2246	addql	#4,d0			| compensate for return address
2247	rts
2248
2249	.globl	_getsfc, _getdfc
2250_getsfc:
2251	movc	sfc,d0
2252	rts
2253_getdfc:
2254	movc	dfc,d0
2255	rts
2256
2257/*
2258 * Load a new user segment table pointer.
2259 */
2260ENTRY(loadustp)
2261#if defined(HP330) || defined(HP360) || defined(HP370) || defined(HP380)
2262	tstl	_mmutype		| HP MMU?
2263	jeq	Lhpmmu9			| yes, skip
2264	movl	sp@(4),d0		| new USTP
2265	moveq	#PGSHIFT,d1
2266	lsll	d1,d0			| convert to addr
2267#if defined(HP380)
2268	cmpl	#-2,_mmutype		| 68040?
2269	jne	LmotommuC		| no, skip
2270	.long	0x4e7b0806		| movc d0,urp
2271	rts
2272LmotommuC:
2273#endif
2274	lea	_protorp,a0		| CRP prototype
2275	movl	d0,a0@(4)		| stash USTP
2276	pmove	a0@,crp			| load root pointer
2277	movl	#DC_CLEAR,d0
2278	movc	d0,cacr			| invalidate on-chip d-cache
2279	rts				|   since pmove flushes TLB
2280Lhpmmu9:
2281#endif
2282#if defined(HP320) || defined(HP350)
2283	MMUADDR(a0)
2284	movl	sp@(4),a0@(MMUUSTP)	| load a new USTP
2285#endif
2286	rts
2287
2288ENTRY(ploadw)
2289#if defined(HP330) || defined(HP360) || defined(HP370)
2290	movl	sp@(4),a0		| address to load
2291	ploadw	#1,a0@			| pre-load translation
2292#endif
2293	rts
2294
2295/*
2296 * Set processor priority level calls.  Most are implemented with
2297 * inline asm expansions.  However, spl0 requires special handling
2298 * as we need to check for our emulated software interrupts.
2299 */
2300
2301ENTRY(spl0)
2302	moveq	#0,d0
2303	movw	sr,d0			| get old SR for return
2304	movw	#PSL_LOWIPL,sr		| restore new SR
2305	tstb	_ssir			| software interrupt pending?
2306	jeq	Lspldone		| no, all done
2307	subql	#4,sp			| make room for RTE frame
2308	movl	sp@(4),sp@(2)		| position return address
2309	clrw	sp@(6)			| set frame type 0
2310	movw	#PSL_LOWIPL,sp@		| and new SR
2311	jra	Lgotsir			| go handle it
2312Lspldone:
2313	rts
2314
2315ENTRY(_insque)
2316	movw	sr,d0
2317	movw	#PSL_HIGHIPL,sr		| atomic
2318	movl	sp@(8),a0		| where to insert (after)
2319	movl	sp@(4),a1		| element to insert (e)
2320	movl	a0@,a1@			| e->next = after->next
2321	movl	a0,a1@(4)		| e->prev = after
2322	movl	a1,a0@			| after->next = e
2323	movl	a1@,a0
2324	movl	a1,a0@(4)		| e->next->prev = e
2325	movw	d0,sr
2326	rts
2327
2328ENTRY(_remque)
2329	movw	sr,d0
2330	movw	#PSL_HIGHIPL,sr		| atomic
2331	movl	sp@(4),a0		| element to remove (e)
2332	movl	a0@,a1
2333	movl	a0@(4),a0
2334	movl	a0,a1@(4)		| e->next->prev = e->prev
2335	movl	a1,a0@			| e->prev->next = e->next
2336	movw	d0,sr
2337	rts
2338
2339/*
2340 * bzero(addr, count)
2341 */
2342ALTENTRY(blkclr, _bzero)
2343ENTRY(bzero)
2344	movl	sp@(4),a0	| address
2345	movl	sp@(8),d0	| count
2346	jeq	Lbzdone		| if zero, nothing to do
2347	movl	a0,d1
2348	btst	#0,d1		| address odd?
2349	jeq	Lbzeven		| no, can copy words
2350	clrb	a0@+		| yes, zero byte to get to even boundary
2351	subql	#1,d0		| decrement count
2352	jeq	Lbzdone		| none left, all done
2353Lbzeven:
2354	movl	d0,d1
2355	andl	#31,d0
2356	lsrl	#5,d1		| convert count to 8*longword count
2357	jeq	Lbzbyte		| no such blocks, zero byte at a time
2358Lbzloop:
2359	clrl	a0@+; clrl	a0@+; clrl	a0@+; clrl	a0@+;
2360	clrl	a0@+; clrl	a0@+; clrl	a0@+; clrl	a0@+;
2361	subql	#1,d1		| one more block zeroed
2362	jne	Lbzloop		| more to go, do it
2363	tstl	d0		| partial block left?
2364	jeq	Lbzdone		| no, all done
2365Lbzbyte:
2366	clrb	a0@+
2367	subql	#1,d0		| one more byte cleared
2368	jne	Lbzbyte		| more to go, do it
2369Lbzdone:
2370	rts
2371
2372/*
2373 * strlen(str)
2374 */
2375ENTRY(strlen)
2376	moveq	#-1,d0
2377	movl	sp@(4),a0	| string
2378Lslloop:
2379	addql	#1,d0		| increment count
2380	tstb	a0@+		| null?
2381	jne	Lslloop		| no, keep going
2382	rts
2383
2384/*
2385 * bcmp(s1, s2, len)
2386 *
2387 * WARNING!  This guy only works with counts up to 64K
2388 */
2389ENTRY(bcmp)
2390	movl	sp@(4),a0		| string 1
2391	movl	sp@(8),a1		| string 2
2392	moveq	#0,d0
2393	movw	sp@(14),d0		| length
2394	jeq	Lcmpdone		| if zero, nothing to do
2395	subqw	#1,d0			| set up for DBcc loop
2396Lcmploop:
2397	cmpmb	a0@+,a1@+		| equal?
2398	dbne	d0,Lcmploop		| yes, keep going
2399	addqw	#1,d0			| +1 gives zero on match
2400Lcmpdone:
2401	rts
2402
2403/*
2404 * {ov}bcopy(from, to, len)
2405 *
2406 * Works for counts up to 128K.
2407 */
2408ALTENTRY(ovbcopy, _bcopy)
2409ENTRY(bcopy)
2410	movl	sp@(12),d0		| get count
2411	jeq	Lcpyexit		| if zero, return
2412	movl	sp@(4),a0		| src address
2413	movl	sp@(8),a1		| dest address
2414	cmpl	a1,a0			| src before dest?
2415	jlt	Lcpyback		| yes, copy backwards (avoids overlap)
2416	movl	a0,d1
2417	btst	#0,d1			| src address odd?
2418	jeq	Lcfeven			| no, go check dest
2419	movb	a0@+,a1@+		| yes, copy a byte
2420	subql	#1,d0			| update count
2421	jeq	Lcpyexit		| exit if done
2422Lcfeven:
2423	movl	a1,d1
2424	btst	#0,d1			| dest address odd?
2425	jne	Lcfbyte			| yes, must copy by bytes
2426	movl	d0,d1			| no, get count
2427	lsrl	#2,d1			| convert to longwords
2428	jeq	Lcfbyte			| no longwords, copy bytes
2429	subql	#1,d1			| set up for dbf
2430Lcflloop:
2431	movl	a0@+,a1@+		| copy longwords
2432	dbf	d1,Lcflloop		| til done
2433	andl	#3,d0			| get remaining count
2434	jeq	Lcpyexit		| done if none
2435Lcfbyte:
2436	subql	#1,d0			| set up for dbf
2437Lcfbloop:
2438	movb	a0@+,a1@+		| copy bytes
2439	dbf	d0,Lcfbloop		| til done
2440Lcpyexit:
2441	rts
2442Lcpyback:
2443	addl	d0,a0			| add count to src
2444	addl	d0,a1			| add count to dest
2445	movl	a0,d1
2446	btst	#0,d1			| src address odd?
2447	jeq	Lcbeven			| no, go check dest
2448	movb	a0@-,a1@-		| yes, copy a byte
2449	subql	#1,d0			| update count
2450	jeq	Lcpyexit		| exit if done
2451Lcbeven:
2452	movl	a1,d1
2453	btst	#0,d1			| dest address odd?
2454	jne	Lcbbyte			| yes, must copy by bytes
2455	movl	d0,d1			| no, get count
2456	lsrl	#2,d1			| convert to longwords
2457	jeq	Lcbbyte			| no longwords, copy bytes
2458	subql	#1,d1			| set up for dbf
2459Lcblloop:
2460	movl	a0@-,a1@-		| copy longwords
2461	dbf	d1,Lcblloop		| til done
2462	andl	#3,d0			| get remaining count
2463	jeq	Lcpyexit		| done if none
2464Lcbbyte:
2465	subql	#1,d0			| set up for dbf
2466Lcbbloop:
2467	movb	a0@-,a1@-		| copy bytes
2468	dbf	d0,Lcbbloop		| til done
2469	rts
2470
2471/*
2472 * Emulate fancy VAX string operations:
2473 *	scanc(count, startc, table, mask)
2474 *	skpc(mask, count, startc)
2475 *	locc(mask, count, startc)
2476 */
2477ENTRY(scanc)
2478	movl	sp@(4),d0	| get length
2479	jeq	Lscdone		| nothing to do, return
2480	movl	sp@(8),a0	| start of scan
2481	movl	sp@(12),a1	| table to compare with
2482	movb	sp@(19),d1	| and mask to use
2483	movw	d2,sp@-		| need a scratch register
2484	clrw	d2		| clear it out
2485	subqw	#1,d0		| adjust for dbra
2486Lscloop:
2487	movb	a0@+,d2		| get character
2488	movb	a1@(0,d2:w),d2	| get table entry
2489	andb	d1,d2		| mask it
2490	dbne	d0,Lscloop	| keep going til no more or non-zero
2491	addqw	#1,d0		| overshot by one
2492	movw	sp@+,d2		| restore scratch
2493Lscdone:
2494	rts
2495
2496ENTRY(skpc)
2497	movl	sp@(8),d0	| get length
2498	jeq	Lskdone		| nothing to do, return
2499	movb	sp@(7),d1	| mask to use
2500	movl	sp@(12),a0	| where to start
2501	subqw	#1,d0		| adjust for dbcc
2502Lskloop:
2503	cmpb	a0@+,d1		| compate with mask
2504	dbne	d0,Lskloop	| keep going til no more or zero
2505	addqw	#1,d0		| overshot by one
2506Lskdone:
2507	rts
2508
2509ENTRY(locc)
2510	movl	sp@(8),d0	| get length
2511	jeq	Llcdone		| nothing to do, return
2512	movb	sp@(7),d1	| mask to use
2513	movl	sp@(12),a0	| where to start
2514	subqw	#1,d0		| adjust for dbcc
2515Llcloop:
2516	cmpb	a0@+,d1		| compate with mask
2517	dbeq	d0,Llcloop	| keep going til no more or non-zero
2518	addqw	#1,d0		| overshot by one
2519Llcdone:
2520	rts
2521
2522/*
2523 * Emulate VAX FFS (find first set) instruction.
2524 */
2525ENTRY(ffs)
2526	moveq	#-1,d0
2527	movl	sp@(4),d1
2528	jeq	Lffsdone
2529Lffsloop:
2530	addql	#1,d0
2531	btst	d0,d1
2532	jeq	Lffsloop
2533Lffsdone:
2534	addql	#1,d0
2535	rts
2536
2537#ifdef FPCOPROC
2538/*
2539 * Save and restore 68881 state.
2540 * Pretty awful looking since our assembler does not
2541 * recognize FP mnemonics.
2542 */
2543ENTRY(m68881_save)
2544	movl	sp@(4),a0		| save area pointer
2545	fsave	a0@			| save state
2546	tstb	a0@			| null state frame?
2547	jeq	Lm68881sdone		| yes, all done
2548	fmovem fp0-fp7,a0@(216)		| save FP general registers
2549	fmovem fpcr/fpsr/fpi,a0@(312)	| save FP control registers
2550Lm68881sdone:
2551	rts
2552
2553ENTRY(m68881_restore)
2554	movl	sp@(4),a0		| save area pointer
2555	tstb	a0@			| null state frame?
2556	jeq	Lm68881rdone		| yes, easy
2557	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
2558	fmovem	a0@(216),fp0-fp7	| restore FP general registers
2559Lm68881rdone:
2560	frestore a0@			| restore state
2561	rts
2562#endif
2563
2564/*
2565 * Handle the nitty-gritty of rebooting the machine.
2566 * Basically we just turn off the MMU and jump to the appropriate ROM routine.
2567 * Note that we must be running in an address range that is mapped one-to-one
2568 * logical to physical so that the PC is still valid immediately after the MMU
2569 * is turned off.  We have conveniently mapped the last page of physical
2570 * memory this way.
2571 */
2572	.globl	_doboot
2573_doboot:
2574#if defined(HP380)
2575	cmpl	#-2,_mmutype		| 68040?
2576	jeq	Lnocache5		| yes, skip
2577#endif
2578	movl	#CACHE_OFF,d0
2579	movc	d0,cacr			| disable on-chip cache(s)
2580#if defined(HP320) || defined(HP350) || defined(HP370)
2581	tstl	_ectype
2582	jeq	Lnocache5
2583	MMUADDR(a0)
2584	andl	#~MMU_CEN,a0@(MMUCMD)	| disable external cache
2585#endif
2586Lnocache5:
2587	lea	MAXADDR,a0		| last page of physical memory
2588	movl	_boothowto,a0@+		| store howto
2589	movl	_bootdev,a0@+		| and devtype
2590	lea	Lbootcode,a1		| start of boot code
2591	lea	Lebootcode,a3		| end of boot code
2592Lbootcopy:
2593	movw	a1@+,a0@+		| copy a word
2594	cmpl	a3,a1			| done yet?
2595	jcs	Lbootcopy		| no, keep going
2596#if defined(HP380)
2597	cmpl	#-2,_mmutype		| 68040?
2598	jne	LmotommuE		| no, skip
2599	.word	0xf4f8			| cpusha bc
2600LmotommuE:
2601#endif
2602	jmp	MAXADDR+8		| jump to last page
2603
2604Lbootcode:
2605	lea	MAXADDR+0x800,sp	| physical SP in case of NMI
2606#if defined(HP380)
2607	cmpl	#-2,_mmutype		| 68040?
2608	jne	LmotommuF		| no, skip
2609	movl	#0,d0
2610	movc	d0,cacr			| caches off
2611	.long	0x4e7b0003		| movc d0,tc
2612	movl	d2,MAXADDR+NBPG-4	| restore old high page contents
2613	jmp	0x1A4			| goto REQ_REBOOT
2614LmotommuF:
2615#endif
2616#if defined(HP330) || defined(HP360) || defined(HP370)
2617	tstl	_mmutype		| HP MMU?
2618	jeq	LhpmmuB			| yes, skip
2619	movl	#0,a0@			| value for pmove to TC (turn off MMU)
2620	pmove	a0@,tc			| disable MMU
2621	jmp	0x1A4			| goto REQ_REBOOT
2622LhpmmuB:
2623#endif
2624#if defined(HP320) || defined(HP350)
2625	MMUADDR(a0)
2626	movl	#0xFFFF0000,a0@(MMUCMD)	| totally disable MMU
2627	movl	d2,MAXADDR+NBPG-4	| restore old high page contents
2628	jmp	0x1A4			| goto REQ_REBOOT
2629#endif
2630Lebootcode:
2631
2632	.data
2633	.globl	_machineid
2634_machineid:
2635	.long	0		| default to 320
2636	.globl	_mmutype,_protorp
2637_mmutype:
2638	.long	0		| default to HP MMU
2639_protorp:
2640	.long	0,0		| prototype root pointer
2641	.globl	_ectype
2642_ectype:
2643	.long	0		| external cache type, default to none
2644	.globl	_internalhpib
2645_internalhpib:
2646	.long	1		| has internal HP-IB, default to yes
2647	.globl	_cold
2648_cold:
2649	.long	1		| cold start flag
2650	.globl	_want_resched
2651_want_resched:
2652	.long	0
2653	.globl	_intiobase, _intiolimit, _extiobase, _CLKbase, _MMUbase
2654	.globl	_proc0paddr
2655_proc0paddr:
2656	.long	0		| KVA of proc0 u-area
2657_intiobase:
2658	.long	0		| KVA of base of internal IO space
2659_intiolimit:
2660	.long	0		| KVA of end of internal IO space
2661_extiobase:
2662	.long	0		| KVA of base of external IO space
2663_CLKbase:
2664	.long	0		| KVA of base of clock registers
2665_MMUbase:
2666	.long	0		| KVA of base of HP MMU registers
2667#ifdef USELEDS
2668heartbeat:
2669	.long	0		| clock ticks since last pulse of heartbeat
2670#endif
2671#ifdef DEBUG
2672	.globl	fulltflush, fullcflush
2673fulltflush:
2674	.long	0
2675fullcflush:
2676	.long	0
2677#endif
2678#ifdef HPFPLIB
2679/*
2680 * Undefined symbols from hpux_float.o:
2681 *
2682 * kdb_printf:	A kernel debugger print routine, we just use printf instead.
2683 * processor:	HP-UX equiv. of machineid, set to 3 if it is a 68040.
2684 * u:		Ye ole u-area.  The code wants to grab the first longword
2685 *		indirect off of that and clear the 0x40000 bit there.
2686 *		Oddly enough this was incorrect even in HP-UX!
2687 * runrun:	Old name for want_resched.
2688 */
2689	.globl	_kdb_printf,_processor,_u,_runrun
2690_kdb_printf:
2691	.long	_printf
2692_processor:
2693	.long	0
2694_u:
2695	.long	.+4
2696	.long	0
2697	.set	_runrun,_want_resched
2698#endif
2699/* interrupt counters */
2700	.globl	_intrcnt,_eintrcnt,_intrnames,_eintrnames
2701_intrnames:
2702	.asciz	"spur"
2703	.asciz	"hil"
2704	.asciz	"lev2"
2705	.asciz	"lev3"
2706	.asciz	"lev4"
2707	.asciz	"lev5"
2708	.asciz	"dma"
2709	.asciz	"clock"
2710	.asciz  "statclock"
2711	.asciz	"nmi"
2712_eintrnames:
2713	.even
2714_intrcnt:
2715	.long	0,0,0,0,0,0,0,0,0,0
2716_eintrcnt:
2717