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