xref: /netbsd/sys/arch/amiga/amiga/locore.s (revision bf9ec67e)
1/*	$NetBSD: locore.s,v 1.131 2002/02/13 16:34:05 is Exp $	*/
2
3/*
4 * Copyright (c) 1988 University of Utah.
5 * Copyright (c) 1980, 1990 The Regents of the University of California.
6 * All rights reserved.
7 *
8 * This code is derived from software contributed to Berkeley by
9 * the Systems Programming Group of the University of Utah Computer
10 * Science Department.
11 *
12 * Redistribution and use in source and binary forms, with or without
13 * modification, are permitted provided that the following conditions
14 * are met:
15 * 1. Redistributions of source code must retain the above copyright
16 *    notice, this list of conditions and the following disclaimer.
17 * 2. Redistributions in binary form must reproduce the above copyright
18 *    notice, this list of conditions and the following disclaimer in the
19 *    documentation and/or other materials provided with the distribution.
20 * 3. All advertising materials mentioning features or use of this software
21 *    must display the following acknowledgement:
22 *	This product includes software developed by the University of
23 *	California, Berkeley and its contributors.
24 * 4. Neither the name of the University nor the names of its contributors
25 *    may be used to endorse or promote products derived from this software
26 *    without specific prior written permission.
27 *
28 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
29 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
30 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
31 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
32 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
33 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
34 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
35 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
36 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
37 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
38 * SUCH DAMAGE.
39 *
40 * from: Utah $Hdr: locore.s 1.58 91/04/22$
41 *
42 *	@(#)locore.s	7.11 (Berkeley) 5/9/91
43 *
44 * Original (hp300) Author: unknown, maybe Mike Hibler?
45 * Amiga author: Markus Wild
46 * Other contributors: Bryan Ford (kernel reload stuff)
47 */
48
49#include "opt_bb060stupidrom.h"
50#include "opt_p5ppc68kboard.h"
51#include "opt_compat_netbsd.h"
52#include "opt_compat_svr4.h"
53#include "opt_compat_sunos.h"
54#include "opt_fpsp.h"
55#include "opt_kgdb.h"
56#include "opt_lockdebug.h"
57
58#include "opt_lev6_defer.h"
59
60#include "assym.h"
61#include <machine/asm.h>
62#include <machine/trap.h>
63
64	.text
65GLOBAL(kernel_text)
66L_base:
67	.long	0x4ef80400+NBPG	/* jmp jmp0.w */
68	.fill	NBPG/4-1,4,0/*xdeadbeef*/
69
70#include <amiga/amiga/vectors.s>
71#include <amiga/amiga/custom.h>
72
73#ifdef DRACO
74#include <amiga/amiga/drcustom.h>
75#endif
76
77#define CIAAADDR(ar)	movl	_C_LABEL(CIAAbase),ar
78#define CIABADDR(ar)	movl	_C_LABEL(CIABbase),ar
79#define CUSTOMADDR(ar)	movl	_C_LABEL(CUSTOMbase),ar
80#define INTREQRADDR(ar)	movl	_C_LABEL(INTREQRaddr),ar
81#define INTREQWADDR(ar)	movl	_C_LABEL(INTREQWaddr),ar
82#define INTENAWADDR(ar) movl	_C_LABEL(amiga_intena_write),ar
83#define	INTENARADDR(ar)	movl	_C_LABEL(amiga_intena_read),ar
84
85	.text
86/*
87 * This is where we wind up if the kernel jumps to location 0.
88 * (i.e. a bogus PC)  This is known to immediately follow the vector
89 * table and is hence at 0x400 (see reset vector in vectors.s).
90 */
91	pea	Ljmp0panic
92	jbsr	_C_LABEL(panic)
93	/* NOTREACHED */
94Ljmp0panic:
95	.asciz	"kernel jump to zero"
96	.even
97
98/*
99 * Do a dump.
100 * Called by auto-restart.
101 */
102ENTRY_NOPROFILE(doadump)
103	jbsr	_C_LABEL(dumpsys)
104	jbsr	_C_LABEL(doboot)
105	/*NOTREACHED*/
106
107/*
108 * Trap/interrupt vector routines
109 */
110#include <m68k/m68k/trap_subr.s>
111
112#if defined(M68040) || defined(M68060)
113ENTRY_NOPROFILE(addrerr4060)
114	clrl	%sp@-			| stack adjust count
115	moveml	%d0-%d7/%a0-%a7,%sp@-	| save user registers
116	movl	%usp,%a0		| save the user SP
117	movl	%a0,%sp@(FR_SP)		|   in the savearea
118	movl	%sp@(FR_HW+8),%sp@-
119	clrl	%sp@-			| dummy code
120	movl	#T_ADDRERR,%sp@-	| mark address error
121	jra	_ASM_LABEL(faultstkadj)	| and deal with it
122#endif
123
124#if defined(M68060)
125ENTRY_NOPROFILE(buserr60)
126	clrl	%sp@-			| stack adjust count
127	moveml	%d0-%d7/%a0-%a7,%sp@-	| save user registers
128	movl	%usp,%a0		| save the user SP
129	movl	%a0,%sp@(FR_SP)		|   in the savearea
130	movel	%sp@(FR_HW+12),%d0	| FSLW
131	btst	#2,%d0			| branch prediction error?
132	jeq	Lnobpe
133	movc	%cacr,%d2
134	orl	#IC60_CABC,%d2		| clear all branch cache entries
135	movc	%d2,%cacr
136	movl	%d0,%d1
137	addql	#1,L60bpe
138	andl	#0x7ffd,%d1
139	jeq	_ASM_LABEL(faultstkadjnotrap2)
140Lnobpe:
141| we need to adjust for misaligned addresses
142	movl	%sp@(FR_HW+8),%d1	| grab VA
143	btst	#27,%d0			| check for mis-aligned access
144	jeq	Lberr3			| no, skip
145	addl	#28,%d1			| yes, get into next page
146					| operand case: 3,
147					| instruction case: 4+12+12
148	andl	#PG_FRAME,%d1           | and truncate
149Lberr3:
150	movl	%d1,%sp@-
151	movl	%d0,%sp@-		| code is FSLW now.
152	andw	#0x1f80,%d0
153	jeq	Lisberr
154	movl	#T_MMUFLT,%sp@-		| show that we are an MMU fault
155	jra	_ASM_LABEL(faultstkadj)	| and deal with it
156#endif
157#if defined(M68040)
158ENTRY_NOPROFILE(buserr40)
159	clrl	%sp@-			| stack adjust count
160	moveml	%d0-%d7/%a0-%a7,%sp@-	| save user registers
161	movl	%usp,%a0		| save the user SP
162	movl	%a0,%sp@(FR_SP)		|   in the savearea
163	movl	%sp@(FR_HW+20),%d1	| get fault address
164	moveq	#0,%d0
165	movw	%sp@(FR_HW+12),%d0	| get SSW
166	btst	#11,%d0			| check for mis-aligned
167	jeq	Lbe1stpg		| no skip
168	addl	#3,%d1			| get into next page
169	andl	#PG_FRAME,%d1		| and truncate
170Lbe1stpg:
171	movl	%d1,%sp@-		| pass fault address.
172	movl	%d0,%sp@-		| pass SSW as code
173	btst	#10,%d0			| test ATC
174	jeq	Lisberr			| it is a bus error
175	movl	#T_MMUFLT,%sp@-		| show that we are an MMU fault
176	jra	_ASM_LABEL(faultstkadj)	| and deal with it
177#endif
178
179ENTRY_NOPROFILE(buserr)
180ENTRY_NOPROFILE(addrerr)
181#if !(defined(M68020) || defined(M68030))
182	jra	_C_LABEL(badtrap)
183#else
184	clrl	%sp@-			| stack adjust count
185	moveml	%d0-%d7/%a0-%a7,%sp@-	| save user registers
186	movl	%usp,%a0		| save the user SP
187	movl	%a0,%sp@(FR_SP)		|   in the savearea
188	moveq	#0,%d0
189	movw	%sp@(FR_HW+10),%d0	| grab SSW for fault processing
190	btst	#12,%d0			| RB set?
191	jeq	LbeX0			| no, test RC
192	bset	#14,%d0			| yes, must set FB
193	movw	%d0,%sp@(FR_HW+10)	| for hardware too
194LbeX0:
195	btst	#13,%d0			| RC set?
196	jeq	LbeX1			| no, skip
197	bset	#15,%d0			| yes, must set FC
198	movw	%d0,%sp@(FR_HW+10)	| for hardware too
199LbeX1:
200	btst	#8,%d0			| data fault?
201	jeq	Lbe0			| no, check for hard cases
202	movl	%sp@(FR_HW+16),%d1	| fault address is as given in frame
203	jra	Lbe10			| thats it
204Lbe0:
205	btst	#4,%sp@(FR_HW+6)	| long (type B) stack frame?
206	jne	Lbe4			| yes, go handle
207	movl	%sp@(FR_HW+2),%d1	| no, can use save PC
208	btst	#14,%d0			| FB set?
209	jeq	Lbe3			| no, try FC
210	addql	#4,%d1			| yes, adjust address
211	jra	Lbe10			| done
212Lbe3:
213	btst	#15,%d0			| FC set?
214	jeq	Lbe10			| no, done
215	addql	#2,%d1			| yes, adjust address
216	jra	Lbe10			| done
217Lbe4:
218	movl	%sp@(FR_HW+36),%d1	| long format, use stage B address
219	btst	#15,%d0			| FC set?
220	jeq	Lbe10			| no, all done
221	subql	#2,%d1			| yes, adjust address
222Lbe10:
223	movl	%d1,%sp@-		| push fault VA
224	movl	%d0,%sp@-		| and padded SSW
225	movw	%sp@(FR_HW+8+6),%d0	| get frame format/vector offset
226	andw	#0x0FFF,%d0		| clear out frame format
227	cmpw	#12,%d0			| address error vector?
228	jeq	Lisaerr			| yes, go to it
229	movl	%d1,%a0			| fault address
230	movl	%sp@,%d0		| function code from ssw
231	btst	#8,%d0			| data fault?
232	jne	Lbe10a
233	movql	#1,%d0			| user program access FC
234					| (we dont separate data/program)
235	btst	#5,%sp@(FR_HW+8)	| supervisor mode?
236	jeq	Lbe10a			| if no, done
237	movql	#5,%d0			| else supervisor program access
238Lbe10a:
239	ptestr	%d0,%a0@,#7		| do a table search
240	pmove	%psr,%sp@		| save result
241	movb	%sp@,%d1
242	btst	#2,%d1			| invalid (incl. limit viol. and berr)?
243	jeq	Lmightnotbemerr		| no -> wp check
244	btst	#7,%d1			| is it MMU table berr?
245	jeq	Lismerr			| no, must be fast
246	jra	Lisberr1		| real bus err needs not be fast.
247Lmightnotbemerr:
248	btst	#3,%d1			| write protect bit set?
249	jeq	Lisberr1		| no: must be bus error
250	movl	%sp@,%d0		| ssw into low word of d0
251	andw	#0xc0,%d0		| Write protect is set on page:
252	cmpw	#0x40,%d0		| was it read cycle?
253	jeq	Lisberr1		| yes, was not WPE, must be bus err
254Lismerr:
255	movl	#T_MMUFLT,%sp@-		| show that we are an MMU fault
256	jra	_ASM_LABEL(faultstkadj)	| and deal with it
257Lisaerr:
258	movl	#T_ADDRERR,%sp@-	| mark address error
259	jra	_ASM_LABEL(faultstkadj)	| and deal with it
260Lisberr1:
261	clrw	%sp@			| re-clear pad word
262#endif
263Lisberr:				| also used by M68040/60
264	tstl	_C_LABEL(nofault)	| device probe?
265	jeq	LberrIsProbe		| no, handle as usual
266	movl	_C_LABEL(nofault),%sp@-	| yes,
267	jbsr	_C_LABEL(longjmp)	|  longjmp(nofault)
268	/* NOTREACHED */
269LberrIsProbe:
270	movl	#T_BUSERR,%sp@-		| mark bus error
271	jra	_ASM_LABEL(faultstkadj)	| and deal with it
272
273/*
274 * FP exceptions.
275 */
276ENTRY_NOPROFILE(fpfline)
277#if defined(M68040)
278	cmpw	#0x202c,%sp@(6)		| format type 2?
279	jne	_C_LABEL(illinst)	| no, not an FP emulation
280#ifdef FPSP
281	jmp	_ASM_LABEL(fpsp_unimp)	| yes, go handle it
282#endif
283#endif
284
285#ifdef FPU_EMULATE
286ENTRY_NOPROFILE(fpemuli)
287	addql	#1,Lfpecnt
288	clrl	%sp@-			| stack adjust count
289	moveml	%d0-%d7/%a0-%a7,%sp@-	| save registers
290	movql	#T_FPEMULI,%d0		| denote as FP emulation trap
291	jra	_ASM_LABEL(fault)	| do it
292#endif
293
294ENTRY_NOPROFILE(fpunsupp)
295#if defined(M68040)
296	cmpl	#MMU_68040,_C_LABEL(mmutype)	| 68040?
297	jne	_C_LABEL(illinst)	| no, treat as illinst
298#ifdef FPSP
299	jmp	_ASM_LABEL(fpsp_unsupp)	| yes, go handle it
300#else
301	clrl	%sp@-			| stack adjust count
302	moveml	%d0-%d7/%a0-%a7,%sp@-	| save registers
303	movql	#T_FPEMULD,%d0		| denote as FP emulation trap
304	jra	_ASM_LABEL(fault)	| do it
305#endif
306#else
307	jra	_C_LABEL(illinst)
308#endif
309/*
310 * Handles all other FP coprocessor exceptions.
311 * Note that since some FP exceptions generate mid-instruction frames
312 * and may cause signal delivery, we need to test for stack adjustment
313 * after the trap call.
314 */
315ENTRY_NOPROFILE(fpfault)
316#ifdef FPCOPROC
317	clrl	%sp@-			| stack adjust count
318	moveml	%d0-%d7/%a0-%a7,%sp@-	| save user registers
319	movl	%usp,%a0		| and save
320	movl	%a0,%sp@(FR_SP)		|   the user stack pointer
321	clrl	%sp@-			| no VA arg
322	movl	_C_LABEL(curpcb),%a0	| current pcb
323	lea	%a0@(PCB_FPCTX),%a0	| address of FP savearea
324	fsave	%a0@			| save state
325#if defined(M68020) || defined(M68030)
326#if defined(M68060) || defined(M68040)
327	movb	_C_LABEL(machineid)+3,%d0
328	andb	#0x90,%d0		| AMIGA_68060 | AMIGA_68040
329	jne	Lfptnull		| XXX
330#endif
331	tstb	%a0@			| null state frame?
332	jeq	Lfptnull		| yes, safe
333	clrw	%d0			| no, need to tweak BIU
334	movb	%a0@(1),%d0		| get frame size
335	bset	#3,%a0@(0,%d0:w)	| set exc_pend bit of BIU
336Lfptnull:
337#endif
338	fmovem	%fpsr,%sp@-		| push fpsr as code argument
339	frestore %a0@			| restore state
340	movl	#T_FPERR,%sp@-		| push type arg
341	jra	_ASM_LABEL(faultstkadj) | call trap and deal with stack cleanup
342#else
343	jra	_C_LABEL(badtrap)	| treat as an unexpected trap
344#endif
345
346/*
347 * Other exceptions only cause four and six word stack frame and require
348 * no post-trap stack adjustment.
349 */
350
351ENTRY_NOPROFILE(badtrap)
352	moveml	%d0/%d1/%a0/%a1,%sp@-	| save scratch regs
353	movw	%sp@(22),%sp@-		| push exception vector info
354	clrw	%sp@-
355	movl	%sp@(22),%sp@-		| and PC
356	jbsr	_C_LABEL(straytrap)	| report
357	addql	#8,%sp			| pop args
358	moveml	%sp@+,%d0/%d1/%a0/%a1	| restore regs
359	jra	_ASM_LABEL(rei)		| all done
360
361ENTRY_NOPROFILE(trap0)
362	clrl	%sp@-			| stack adjust count
363	moveml	%d0-%d7/%a0-%a7,%sp@-	| save user registers
364	movl	%usp,%a0		| save the user SP
365	movl	%a0,%sp@(FR_SP)		|   in the savearea
366	movl	%d0,%sp@-		| push syscall number
367	jbsr	_C_LABEL(syscall)	| handle it
368	addql	#4,%sp			| pop syscall arg
369	movl	%sp@(FR_SP),%a0		| grab and restore
370	movl	%a0,%usp		|   user SP
371	moveml	%sp@+,%d0-%d7/%a0-%a6	| restore most registers
372	addql	#8,%sp			| pop SP and stack adjust
373	jra	_ASM_LABEL(rei)		| all done
374
375/*
376 * Trap 12 is the entry point for the cachectl "syscall"
377 *	cachectl(command, addr, length)
378 * command in d0, addr in a1, length in d1
379 */
380ENTRY_NOPROFILE(trap12)
381	movl	_C_LABEL(curproc),%sp@-	| push current proc pointer
382	movl	%d1,%sp@-		| push length
383	movl	%a1,%sp@-		| push addr
384	movl	%d0,%sp@-		| push command
385	jbsr	_C_LABEL(cachectl1)	| do it
386	lea	%sp@(16),%sp		| pop args
387	jra	_ASM_LABEL(rei)		| all done
388
389/*
390 * Trap 15 is used for:
391 *	- KGDB traps
392 *	- trace traps for SUN binaries (not fully supported yet)
393 * We just pass it on and let trap() sort it all out
394 */
395ENTRY_NOPROFILE(trap15)
396	clrl	%sp@-
397	moveml	%d0-%d7/%a0-%a7,%sp@-
398#ifdef KGDB
399	moveq	#T_TRAP15,%d0
400	movw	%sp@(FR_HW),%d1		| get PSW
401	andw	#PSL_S,%d1		| from user mode?
402	jeq	_ASM_LABEL(fault)	| yes, just a regular fault
403	movl	%d0,%sp@-
404	jbsr	_C_LABEL(kgdb_trap_glue) | returns if no debugger
405	addl	#4,%sp
406#endif
407	moveq	#T_TRAP15,%d0
408	jra	_ASM_LABEL(fault)
409
410/*
411 * Hit a breakpoint (trap 1 or 2) instruction.
412 * Push the code and treat as a normal fault.
413 */
414ENTRY_NOPROFILE(trace)
415	clrl	%sp@-
416	moveml	%d0-%d7/%a0-%a7,%sp@-
417#ifdef KGDB
418	moveq	#T_TRACE,%d0
419	movw	%sp@(FR_HW),%d1		| get SSW
420	andw	#PSL_S,%d1		| from user mode?
421	jeq	_ASM_LABEL(fault)	| no, regular fault
422	movl	%d0,%sp@-
423	jbsr	_C_LABEL(kgdb_trap_glue) | returns if no debugger
424	addl	#4,%sp
425#endif
426	moveq	#T_TRACE,%d0
427	jra	_ASM_LABEL(fault)
428
429/* Use common m68k sigreturn */
430#include <m68k/m68k/sigreturn.s>
431
432/*
433 * Interrupt handlers.
434 *
435 *	Level 0:	Spurious: ignored.
436 *	Level 1:	builtin-RS232 TBE, softint (not used yet)
437 *	Level 2:	keyboard (CIA-A) + DMA + SCSI
438 *	Level 3:	VBL
439 *	Level 4:	not used
440 *	Level 5:	builtin-RS232 RBF
441 *	Level 6:	Clock (CIA-B-Timers), Floppy index pulse
442 *	Level 7:	Non-maskable: shouldn't be possible. ignore.
443 */
444
445/* Provide a generic interrupt dispatcher, only handle hardclock (int6)
446 * and serial RBF (int5) specially, to improve performance
447 */
448
449ENTRY_NOPROFILE(spurintr)
450	addql	#1,_C_LABEL(interrupt_depth)
451	addql	#1,_C_LABEL(intrcnt)+0
452	addql	#1,_C_LABEL(uvmexp)+UVMEXP_INTRS
453	subql	#1,_C_LABEL(interrupt_depth)
454	jra	_ASM_LABEL(rei)
455
456ENTRY_NOPROFILE(lev5intr)
457	addql	#1,_C_LABEL(interrupt_depth)
458	moveml	%d0/%d1/%a0/%a1,%sp@-
459#include "ser.h"
460#if NSER > 0
461	jsr	_C_LABEL(ser_fastint)
462#else
463	INTREQWADDR(%a0)
464	movew	#INTF_RBF,%a0@		| clear RBF interrupt in intreq
465#endif
466	moveml	%sp@+,%d0/%d1/%a0/%a1
467	addql	#1,_C_LABEL(intrcnt)+20
468	addql	#1,_C_LABEL(uvmexp)+UVMEXP_INTRS
469	subql	#1,_C_LABEL(interrupt_depth)
470	jra	_ASM_LABEL(rei)
471
472#ifdef DRACO
473ENTRY_NOPROFILE(DraCoLev2intr)
474	addql	#1,_C_LABEL(interrupt_depth)
475	moveml	%d0/%d1/%a0/%a1,%sp@-
476
477	CIAAADDR(%a0)
478	movb	%a0@(CIAICR),%d0	| read irc register (clears ints!)
479	jge     Ldrintrcommon		| CIAA IR not set, go through isr chain
480	movel	_C_LABEL(draco_intpen),%a0
481|	andib	#4,%a0@
482|XXX this would better be
483	bclr	#2,%a0@
484	btst	#0,%d0			| timerA interrupt?
485	jeq	Ldraciaend
486
487	lea	%sp@(16),%a1		| get pointer to PS
488	movl	%a1,%sp@-		| push pointer to PS, PC
489
490	movw	#PSL_HIGHIPL,%sr	| hardclock at high IPL
491	jbsr	_C_LABEL(hardclock)	| call generic clock int routine
492	addql	#4,%sp			| pop params
493	addql	#1,_C_LABEL(intrcnt)+32	| add another system clock interrupt
494
495Ldraciaend:
496	moveml	%sp@+,%d0/%d1/%a0/%a1
497	addql	#1,_C_LABEL(uvmexp)+UVMEXP_INTRS
498	subql	#1,_C_LABEL(interrupt_depth)
499	jra	_ASM_LABEL(rei)
500
501/* XXX on the DraCo rev. 4 or later, lev 1 is vectored here. */
502ENTRY_NOPROFILE(DraCoLev1intr)
503	addql	#1,_C_LABEL(interrupt_depth)
504	moveml	%d0/%d1/%a0/%a1,%sp@-
505	movl	_C_LABEL(draco_ioct),%a0
506	btst	#5,%a0@(7)
507	jeq	Ldrintrcommon
508	btst	#4,%a0@(7)	| this only happens during autoconfiguration,
509	jeq	Ldrintrcommon	| so test last.
510	movw	#PSL_HIGHIPL,%sr	| run clock at high ipl
511Ldrclockretry:
512	lea	%sp@(16),%a1	| get pointer to PS
513	movl	%a1,%sp@-	| push pointer to PS, PC
514	jbsr	_C_LABEL(hardclock)
515	addql	#4,%sp		| pop params
516	addql	#1,_C_LABEL(intrcnt)+32	| add another system clock interrupt
517
518	movl	_C_LABEL(draco_ioct),%a0
519	tstb	%a0@(9)		| latch timer value
520	movw	%a0@(11),%d0	| can't use movpw here, might be 68060
521	movb	%a0@(13),%d0
522	addw	_C_LABEL(amiga_clk_interval)+2,%d0
523	movb	%d0,%a0@(13)	| low byte: latch write value
524	movw	%d0,%a0@(11)	| ...and write it into timer
525	tstw	%d0		| already positive?
526	jcs	Ldrclockretry	| we lost more than one tick, call us again.
527
528	clrb	%a0@(9)		| reset timer irq
529
530	moveml	%sp@+,%d0/%d1/%a0/%a1
531	addql	#1,_C_LABEL(uvmexp)+UVMEXP_INTRS
532	subql	#1,_C_LABEL(interrupt_depth)
533	jra	_ASM_LABEL(rei)	| XXXX: shouldn't we call the normal lev1?
534
535/* XXX on the DraCo, lev 1, 3, 4, 5 and 6 are vectored here by initcpu() */
536ENTRY_NOPROFILE(DraCoIntr)
537	addql	#1,_C_LABEL(interrupt_depth)
538	moveml  %d0/%d1/%a0/%a1,%sp@-
539Ldrintrcommon:
540	lea	_ASM_LABEL(Drintrcnt)-4,%a0
541	movw	%sp@(22),%d0		| use vector offset
542	andw	#0xfff,%d0		|   sans frame type
543	addql	#1,%a0@(-0x60,%d0:w)	|     to increment apropos counter
544	movw	%sr,%sp@-		| push current SR value
545	clrw	%sp@-			|    padded to longword
546	jbsr	_C_LABEL(intrhand)	| handle interrupt
547	addql	#4,%sp			| pop SR
548	moveml	%sp@+,%d0/%d1/%a0/%a1
549	addql	#1,_C_LABEL(uvmexp)+UVMEXP_INTRS
550	subql	#1,_C_LABEL(interrupt_depth)
551	jra	_ASM_LABEL(rei)
552#endif
553
554
555ENTRY_NOPROFILE(lev1intr)
556ENTRY_NOPROFILE(lev2intr)
557ENTRY_NOPROFILE(lev3intr)
558#ifndef LEV6_DEFER
559ENTRY_NOPROFILE(lev4intr)
560#endif
561	addql	#1,_C_LABEL(interrupt_depth)
562	moveml	%d0/%d1/%a0/%a1,%sp@-
563Lintrcommon:
564	lea	_C_LABEL(intrcnt),%a0
565	movw	%sp@(22),%d0		| use vector offset
566	andw	#0xfff,%d0		|   sans frame type
567	addql	#1,%a0@(-0x60,%d0:w)	|     to increment apropos counter
568	movw	%sr,%sp@-		| push current SR value
569	clrw	%sp@-			|    padded to longword
570	jbsr	_C_LABEL(intrhand)	| handle interrupt
571	addql	#4,%sp			| pop SR
572	moveml	%sp@+,%d0/%d1/%a0/%a1
573	addql	#1,_C_LABEL(uvmexp)+UVMEXP_INTRS
574	subql	#1,_C_LABEL(interrupt_depth)
575	jra	_ASM_LABEL(rei)
576
577/* XXX used to be ifndef DRACO; vector will be overwritten by initcpu() */
578
579ENTRY_NOPROFILE(lev6intr)
580#ifdef LEV6_DEFER
581	/*
582	 * cause a level 4 interrupt (AUD3) to occur as soon
583	 * as we return. Block generation of level 6 ints until
584	 * we have dealt with this one.
585	 */
586	addql	#1,_C_LABEL(interrupt_depth)
587	moveml	%d0/%a0,%sp@-
588	INTREQRADDR(%a0)
589	movew	%a0@,%d0
590	btst	#INTB_EXTER,%d0
591	jeq	Llev6spur
592	INTREQWADDR(%a0)
593	movew	#INTF_SETCLR+INTF_AUD3,%a0@
594	INTENAWADDR(%a0)
595	movew	#INTF_EXTER,%a0@
596	movew	#INTF_SETCLR+INTF_AUD3,%a0@	| make sure THIS one is ok...
597	moveml	%sp@+,%d0/%a0
598	subql	#1,_C_LABEL(interrupt_depth)
599	rte
600Llev6spur:
601	addql	#1,_C_LABEL(intrcnt)+36	| count spurious level 6 interrupts
602	moveml	%sp@+,%d0/%a0
603	subql	#1,_C_LABEL(interrupt_depth)
604	rte
605
606ENTRY_NOPROFILE(lev4intr)
607ENTRY_NOPROFILE(fake_lev6intr)
608#endif
609	addql	#1,_C_LABEL(interrupt_depth)
610	moveml	%d0/%d1/%a0/%a1,%sp@-
611#ifdef LEV6_DEFER
612	/*
613	 * check for fake level 6
614	 */
615	INTREQRADDR(%a0)
616	movew	%a0@,%d0
617	btst	#INTB_EXTER,%d0
618	jeq	Lintrcommon		| if EXTER not pending, handle normally
619#endif
620
621	CIABADDR(%a0)
622	movb	%a0@(CIAICR),%d0	| read irc register (clears ints!)
623	jge	Lchkexter		| CIAB IR not set, go through isr chain
624	INTREQWADDR(%a0)
625#ifndef LEV6_DEFER
626	movew	#INTF_EXTER,%a0@	| clear EXTER interrupt in intreq
627#else
628	movew	#INTF_EXTER+INTF_AUD3,%a0@ | clear EXTER & AUD3 in intreq
629	INTENAWADDR(%a0)
630	movew	#INTF_SETCLR+INTF_EXTER,%a0@ | reenable EXTER interrupts
631#endif
632	btst	#0,%d0			| timerA interrupt?
633	jeq     Ltstciab4		| no
634	movl	%d0,%sp@-		| push CIAB interrupt flags
635	lea	%sp@(20),%a1		| get pointer to PS
636	movl	%a1,%sp@-		| push pointer to PS, PC
637	jbsr	_C_LABEL(hardclock)	| call generic clock int routine
638	addql	#4,%sp			| pop params
639	addql	#1,_C_LABEL(intrcnt)+32	| add another system clock interrupt
640	movl	%sp@+,%d0		| pop interrupt flags
641Ltstciab4:
642#include "fd.h"
643#if NFD > 0
644	btst	#4,%d0			| FLG (dskindex) interrupt?
645	jeq	Lskipciab		| no
646	jbsr	_C_LABEL(fdidxintr)	| tell floppy driver we got it
647Lskipciab:
648#endif
649| other ciab interrupts?
650Llev6done:
651	moveml	%sp@+,%d0/%d1/%a0/%a1	| restore scratch regs
652	addql	#1,_C_LABEL(uvmexp)+UVMEXP_INTRS
653	subql	#1,_C_LABEL(interrupt_depth)
654	jra	_ASM_LABEL(rei)		| all done [can we do rte here?]
655Lchkexter:
656| check to see if EXTER request is really set?
657	movl	_C_LABEL(isr_exter),%a0	| get head of EXTER isr chain
658Lnxtexter:
659	movl	%a0,%d0			| test if any more entries
660	jeq	Lexterdone		| (spurious interrupt?)
661	movl	%a0,%sp@-		| save isr pointer
662	movl	%a0@(ISR_ARG),%sp@-
663	movl	%a0@(ISR_INTR),%a0
664	jsr	%a0@			| call isr handler
665	addql	#4,%sp
666	movl	%sp@+,%a0		| restore isr pointer
667	movl	%a0@(ISR_FORW),%a0	| get next pointer
668	tstl	%d0			| did handler process the int?
669	jeq	Lnxtexter		| no, try next
670Lexterdone:
671	INTREQWADDR(%a0)
672#ifndef LEV6_DEFER
673	movew	#INTF_EXTER,%a0@	| clear EXTER interrupt
674#else
675	movew	#INTF_EXTER+INTF_AUD3,%a0@ | clear EXTER & AUD3 interrupt
676	INTENAWADDR(%a0)
677	movew	#INTF_SETCLR+INTF_EXTER,%a0@ | reenable EXTER interrupts
678#endif
679	addql	#1,_C_LABEL(intrcnt)+24	| count EXTER interrupts
680	jra	Llev6done
681/* XXX endifndef DRACO used to be here */
682
683ENTRY_NOPROFILE(lev7intr)
684	addql	#1,_C_LABEL(intrcnt)+28
685	/*
686	 * some amiga zorro2 boards seem to generate spurious NMIs. Best
687	 * thing to do is to return as quick as possible. That's the
688	 * reason why I do RTE here instead of jra rei.
689	 */
690	rte				| all done
691
692
693/*
694 * Emulation of VAX REI instruction.
695 *
696 * This code deals with checking for and servicing ASTs
697 * (profiling, scheduling) and software interrupts (network, softclock).
698 * We check for ASTs first, just like the VAX.  To avoid excess overhead
699 * the T_ASTFLT handling code will also check for software interrupts so we
700 * do not have to do it here.
701 * do not have to do it here.  After identifing that we need an AST we
702 * drop the IPL to allow device interrupts.
703 *
704 * This code is complicated by the fact that sendsig may have been called
705 * necessitating a stack cleanup.  A cleanup should only be needed at this
706 * point for coprocessor mid-instruction frames (type 9), but we also test
707 * for bus error frames (type 10 and 11).
708 */
709ASENTRY_NOPROFILE(rei)
710#ifdef DEBUG
711	tstl	_C_LABEL(panicstr)	| have we paniced?
712	jne	Ldorte			| yes, do not make matters worse
713#endif
714	tstl	_C_LABEL(astpending)	| AST pending?
715	jeq	Ldorte			| no, done
716Lrei1:
717	btst	#5,%sp@			| yes, are we returning to user mode?
718	jne	Ldorte			| no, done
719	movw	#PSL_LOWIPL,%sr		| lower SPL
720	clrl	%sp@-			| stack adjust
721	moveml	%d0-%d7/%a0-%a7,%sp@-	| save all registers
722	movl	%usp,%a1		| including
723	movl	%a1,%sp@(FR_SP)		|    the users SP
724	clrl	%sp@-			| VA == none
725	clrl	%sp@-			| code == none
726	movl	#T_ASTFLT,%sp@-		| type == async system trap
727	jbsr	_C_LABEL(trap)		| go handle it
728	lea	%sp@(12),%sp		| pop value args
729	movl	%sp@(FR_SP),%a0		| restore user SP
730	movl	%a0,%usp		|   from save area
731	movw	%sp@(FR_ADJ),%d0	| need to adjust stack?
732	jne	Laststkadj		| yes, go to it
733	moveml	%sp@+,%d0-%d7/%a0-%a6	| no, restore most user regs
734	addql	#8,%sp			| toss SP and stack adjust
735	rte				| and do real RTE
736Laststkadj:
737	lea	%sp@(FR_HW),%a1		| pointer to HW frame
738	addql	#8,%a1			| source pointer
739	movl	%a1,%a0			| source
740	addw	%d0,%a0			|  + hole size = dest pointer
741	movl	%a1@-,%a0@-		| copy
742	movl	%a1@-,%a0@-		|  8 bytes
743	movl	%a0,%sp@(FR_SP)		| new SSP
744	moveml	%sp@+,%d0-%d7/%a0-%a6	| restore user registers
745	movl	%sp@,%sp		| and our SP
746Ldorte:
747	rte				| real return
748
749/*
750 * Kernel access to the current processes kernel stack is via a fixed
751 * virtual address.  It is at the same address as in the users VA space.
752 */
753BSS(esym,4)
754
755
756/*
757 * Initialization
758 *
759 * A5 contains physical load point from boot
760 * exceptions vector thru our table, that's bad.. just hope nothing exceptional
761 * happens till we had time to initialize ourselves..
762 */
763BSS(lowram,4)
764
765#define	RELOC(var, ar)			\
766	lea	_C_LABEL(var),ar;	\
767	addl	%a5,ar
768
769#define	ASRELOC(var, ar)		\
770	lea	_ASM_LABEL(var),ar;	\
771	addl	%a5,ar
772
773	.text
774
775	| XXX should be a symbol?
776	| 2: needs a4 = esym
777	| 3: no chipmem requirement
778	|    bootinfo data structure
779
780	.word	0
781	.word	0x0003			| loadbsd version required
782ASENTRY_NOPROFILE(start)
783	lea	%pc@(L_base),%a5	| initialize relocation register
784
785	movw	#PSL_HIGHIPL,%sr	| no interrupts
786	ASRELOC(tmpstk,%a6)
787	movl	%a6,%sp			| give ourselves a temporary stack
788
789	| save the passed parameters. "prepass" them on the stack for
790	| later catch by start_c()
791	movl	%d6,%sp@-		| pass boot partition offset
792	movl	%a2,%sp@-		| pass sync inhibit flags
793	movl	%d3,%sp@-		| pass AGA mode
794	movl	%a4,%sp@-		| pass address of _esym
795	movl	%d1,%sp@-		| pass chipmem-size
796	movl	%d0,%sp@-		| pass fastmem-size
797	movl	%a0,%sp@-		| pass fastmem_start
798	movl	%d5,%sp@-		| pass machine id
799
800	/*
801	 * initialize some hw addresses to their physical address
802	 * for early running
803	 */
804#ifdef DRACO
805	/*
806	 * this is already dynamically done on DraCo
807	 */
808	cmpb	#0x7D,%sp@
809	jne	LisAmiga1
810| debug code:
811| we should need about 1 uSec for the loop.
812| we dont need the AGA mode register.
813	movel	#100000,%d3
814LisDraco0:
815#ifdef DEBUG_KERNEL_START
816	movb	#0,0x200003c8
817	movb	#00,0x200003c9
818	movb	#40,0x200003c9
819	movb	#00,0x200003c9
820|XXX:
821	movb	#0,0x200003c8
822	movb	#40,0x200003c9
823	movb	#00,0x200003c9
824	movb	#00,0x200003c9
825	subql	#1,%d3
826	jcc	LisDraco0
827#endif
828
829	RELOC(chipmem_start, %a0)
830	movl	#0,%a0@
831
832	RELOC(CIAAbase, %a0)
833	movl	#0x2801001, %a0@
834	RELOC(CIABbase, %a0)
835	movl	#0x2800000, %a0@
836
837	/* XXXX more to come here; as we need it */
838
839	jra	LisDraco1
840LisAmiga1:
841#endif
842	RELOC(chipmem_start, %a0)
843	movl	#0x400,%a0@
844	RELOC(CIAAbase, %a0)
845	movl	#0xbfe001,%a0@
846	RELOC(CIABbase, %a0)
847	movl	#0xbfd000,%a0@
848	RELOC(CUSTOMbase, %a0)
849	movl	#0xdff000,%a0@
850
851#ifdef DRACO
852LisDraco1:
853#endif
854	/*
855	 * initialize the timer frequency
856	 */
857	RELOC(eclockfreq, %a0)
858	movl	%d4,%a0@
859
860	movl	#AMIGA_68030,%d1	| 68030 Attn flag from exec
861	andl	%d5,%d1
862	jeq	Ltestfor020
863	RELOC(mmutype, %a0)
864	movl	#MMU_68030,%a0@		| assume 020 means 851
865	RELOC(cputype, %a0)
866	movl	#CPU_68030,%a0@
867	jra	Lsetcpu040		| skip to init.
868Ltestfor020:
869	movl	#AMIGA_68020,%d1	| 68020 Attn flag from exec
870	andl	%d5,%d1
871	jeq	Lsetcpu040
872	RELOC(mmutype, %a0)
873	movl	#MMU_68851,%a0@
874	RELOC(cputype, %a0)
875	movl	#CPU_68020,%a0@
876Lsetcpu040:
877	movl	#CACHE_OFF,%d0		| 68020/030 cache
878	movl	#AMIGA_68040,%d1
879	andl	%d1,%d5
880	jeq	Lstartnot040		| it is not 68040
881	RELOC(mmutype, %a0)
882	movl	#MMU_68040,%a0@		| same as hp300 for compat
883	RELOC(cputype, %a0)
884	movl	#CPU_68040,%a0@
885	.word	0xf4f8			| cpusha bc - push and invalidate caches
886	movl	#CACHE40_OFF,%d0	| 68040 cache disable
887#ifndef BB060STUPIDROM
888	btst	#7,%sp@(3)
889	jeq	Lstartnot040
890	movl	#CPU_68060,%a0@		| and in the cputype
891	orl	#IC60_CABC,%d0		| XXX and clear all 060 branch cache
892#else
893	movc	%d0,%cacr
894	bset	#30,%d0			| not allocate data cache bit
895	movc	%d0,%cacr		| does it stick?
896	movc	%cacr,%d0
897	tstl	%d0
898	jeq	Lstartnot040
899	bset	#7,%sp@(3)		| note it is '60 family in machineid
900	movl	#CPU_68060,%a0@		| and in the cputype
901	orl	#IC60_CABC,%d0		| XXX and clear all 060 branch cache
902	.word	0x4e7a,0x1808		| movc	pcr,d1
903	swap	%d1
904	cmpw	#0x430,%d1
905	jne	Lstartnot040		| but no FPU
906	bset	#6,%sp@(3)		| yes, we have FPU, note that
907	swap	%d1
908	bclr	#1,%d1			| ... and switch it on.
909	.word	0x4e7b,0x1808		| movc	d1,pcr
910#endif
911Lstartnot040:
912	movc	%d0,%cacr		| clear and disable on-chip cache(s)
913	movl	#_C_LABEL(vectab),%a0
914	movc	%a0,%vbr
915
916/* initialize source/destination control registers for movs */
917	moveq	#FC_USERD,%d0		| user space
918	movc	%d0,%sfc		|   as source
919	movc	%d0,%dfc		|   and destination of transfers
920
921/* let the C function initialize everything and enable the MMU */
922	RELOC(start_c, %a0)
923	jbsr	%a0@
924	addl	#28,%sp
925	jmp	Lunshadow:l
926
927Lunshadow:
928
929	lea	_ASM_LABEL(tmpstk),%sp	| give ourselves a temporary stack
930	jbsr	_C_LABEL(start_c_cleanup)
931
932/* set kernel stack, user SP, and initial pcb */
933	movl	_C_LABEL(proc0paddr),%a1	| proc0 kernel stack
934	lea	%a1@(USPACE),%sp	| set kernel stack to end of area
935	lea	_C_LABEL(proc0),%a2	| initialize proc0.p_addr so that
936	movl	%a1,%a2@(P_ADDR)	|   we don't dref NULL in trap()
937	movl	#USRSTACK-4,%a2
938	movl	%a2,%usp		| init user SP
939	movl	%a2,%a1@(PCB_USP)	| and save it
940	movl	%a1,_C_LABEL(curpcb)	| proc0 is running
941	clrw	%a1@(PCB_FLAGS)		| clear flags
942#ifdef FPCOPROC
943	clrl	%a1@(PCB_FPCTX)		| ensure null FP context
944|WRONG!	movl	%a1,%sp@-
945|	pea	%a1@(PCB_FPCTX)
946|	jbsr	_C_LABEL(m68881_restore)	| restore it (does not kill a1)
947|	addql	#4,%sp
948#endif
949/* flush TLB and turn on caches */
950
951
952	jbsr	_ASM_LABEL(__TBIA)	| invalidate TLB
953	movl	#CACHE_ON,%d0
954	tstl	%d5
955	jeq	Lcacheon
956| is this needed? MLH
957	.word	0xf4f8		| cpusha bc - push & invalidate caches
958	movl	#CACHE40_ON,%d0
959#ifdef M68060
960	cmpl	#CPU_68060,_C_LABEL(cputype)
961	jne	Lcacheon
962	movl	#CACHE60_ON,%d0
963#endif
964Lcacheon:
965	movc	%d0,%cacr		| clear cache(s)
966/* final setup for C code */
967
968	movw	#PSL_LOWIPL,%sr		| lower SPL
969
970	movl	%d7,_C_LABEL(boothowto)	| save reboot flags
971/*
972 * Create a fake exception frame that returns to user mode,
973 * make space for the rest of a fake saved register set, and
974 * pass the first available RAM and a pointer to the register
975 * set to "main()".  "main()" will do an "execve()" using that
976 * stack frame.
977 * When "main()" returns, we're running in process 1 and have
978 * successfully executed the "execve()".  We load up the registers from
979 * that set; the "rte" loads the PC and PSR, which jumps to "init".
980 */
981  	clrw	%sp@-			| vector offset/frame type
982	clrl	%sp@-			| PC - filled in by "execve"
983  	movw	#PSL_USER,%sp@-		| in user mode
984	clrl	%sp@-			| stack adjust count
985	lea	%sp@(-64),%sp		| construct space for D0-D7/A0-A7
986	lea	_C_LABEL(proc0),%a0		| proc0 in a0
987	movl	%sp,%a0@(P_MD + MD_REGS)	| save frame for proc0
988	movl	%usp,%a1
989	movl	%a1,%sp@(FR_SP)		| save user stack pointer in frame
990	pea	%sp@			| addr of space for D0
991
992	jbsr	_C_LABEL(main)		| main(firstaddr, r0)
993	addql	#4,%sp			| pop args
994
995	cmpl	#MMU_68040,_C_LABEL(mmutype)	| 68040?
996	jne	Lnoflush		| no, skip
997	.word	0xf478			| cpusha dc
998	.word	0xf498			| cinva ic, also clears the 060 btc
999Lnoflush:
1000	movl	%sp@(FR_SP),%a0		| grab and load
1001	movl	%a0,%usp		|   user SP
1002	moveml	%sp@+,%d0-%d7/%a0-%a6	| load most registers (all but SSP)
1003	addql	#8,%sp			| pop SSP and stack adjust count
1004  	rte
1005
1006/*
1007 * proc_trampoline call function in register a2 with a3 as an arg
1008 * and then rei.
1009 */
1010ENTRY_NOPROFILE(proc_trampoline)
1011	movl	%a3,%sp@-		| push function arg
1012	jbsr	%a2@			| call function
1013	addql	#4,%sp			| pop arg
1014	movl	%sp@(FR_SP),%a0		| usp to a0
1015	movl	%a0,%usp		| setup user stack pointer
1016	moveml	%sp@+,%d0-%d7/%a0-%a6	| restore all but sp
1017	addql	#8,%sp			| pop sp and stack adjust
1018	jra	_ASM_LABEL(rei)		| all done
1019
1020/*
1021 * Use common m68k sigcode.
1022 */
1023#include <m68k/m68k/sigcode.s>
1024#ifdef COMPAT_SUNOS
1025#include <m68k/m68k/sunos_sigcode.s>
1026#endif
1027#ifdef COMPAT_SVR4
1028#include <m68k/m68k/svr4_sigcode.s>
1029#endif
1030
1031/*
1032 * Primitives
1033 */
1034
1035/*
1036 * Use common m68k support routines.
1037 */
1038#include <m68k/m68k/support.s>
1039
1040/*
1041 * update profiling information for the user
1042 * addupc(pc, &u.u_prof, ticks)
1043 */
1044ENTRY(addupc)
1045	movl	%a2,%sp@-		| scratch register
1046	movl	%sp@(12),%a2		| get &u.u_prof
1047	movl	%sp@(8),%d0		| get user pc
1048	subl	%a2@(8),%d0		| pc -= pr->pr_off
1049	jlt	Lauexit			| less than 0, skip it
1050	movl	%a2@(12),%d1		| get pr->pr_scale
1051	lsrl	#1,%d0			| pc /= 2
1052	lsrl	#1,%d1			| scale /= 2
1053	mulul	%d1,%d0			| pc /= scale
1054	moveq	#14,%d1
1055	lsrl	%d1,%d0			| pc >>= 14
1056	bclr	#0,%d0			| pc &= ~1
1057	cmpl	%a2@(4),%d0		| too big for buffer?
1058	jge	Lauexit			| yes, screw it
1059	addl	%a2@,%d0		| no, add base
1060	movl	%d0,%sp@-		| push address
1061	jbsr	_C_LABEL(fusword)	| grab old value
1062	movl	%sp@+,%a0		| grab address back
1063	cmpl	#-1,%d0			| access ok
1064	jeq	Lauerror		| no, skip out
1065	addw	%sp@(18),%d0		| add tick to current value
1066	movl	%d0,%sp@-		| push value
1067	movl	%a0,%sp@-		| push address
1068	jbsr	_C_LABEL(susword)	| write back new value
1069	addql	#8,%sp			| pop params
1070	tstl	%d0			| fault?
1071	jeq	Lauexit			| no, all done
1072Lauerror:
1073	clrl	%a2@(12)		| clear scale (turn off prof)
1074Lauexit:
1075	movl	%sp@+,%a2		| restore scratch reg
1076	rts
1077
1078/*
1079 * non-local gotos
1080 */
1081ENTRY(qsetjmp)
1082	movl	%sp@(4),%a0	| savearea pointer
1083	lea	%a0@(40),%a0	| skip regs we do not save
1084	movl	%a6,%a0@+	| save FP
1085	movl	%sp,%a0@+	| save SP
1086	movl	%sp@,%a0@	| and return address
1087	moveq	#0,%d0		| return 0
1088	rts
1089
1090BSS(want_resched,4)
1091
1092/*
1093 * Use common m68k process manipulation routines.
1094 */
1095#include <m68k/m68k/proc_subr.s>
1096
1097Lsw0:
1098	.asciz	"cpu_switch"
1099	.even
1100
1101	.data
1102GLOBAL(masterpaddr)		| XXX compatibility (debuggers)
1103GLOBAL(curpcb)
1104	.long	0
1105ASGLOBAL(pcbflag)
1106	.byte	0		| copy of pcb_flags low byte
1107#ifdef __ELF__
1108	.align	4
1109#else
1110	.align	2
1111#endif
1112BSS(nullpcb,SIZEOF_PCB)
1113	.text
1114
1115/*
1116 * At exit of a process, do a switch for the last time.
1117 * Switch to a safe stack and PCB, and select a new process to run.  The
1118 * old stack and u-area will be freed by the reaper.
1119 *
1120 * MUST BE CALLED AT SPLHIGH!
1121 */
1122ENTRY(switch_exit)
1123	movl	%sp@(4),%a0
1124	movl	#_C_LABEL(nullpcb),_C_LABEL(curpcb) | save state in garbage pcb
1125	lea	_ASM_LABEL(tmpstk),%sp	| goto a tmp stack
1126
1127	/* Schedule the vmspace and stack to be freed. */
1128	movl	%a0,%sp@-		| exit2(p)
1129	jbsr	_C_LABEL(exit2)
1130	lea	%sp@(4),%sp		| pop args
1131
1132#if defined(LOCKDEBUG)
1133	/* Acquire sched_lock */
1134	jbsr	_C_LABEL(sched_lock_idle)
1135#endif
1136
1137	jra	_C_LABEL(cpu_switch)
1138
1139/*
1140 * When no processes are on the runq, Swtch branches to idle
1141 * to wait for something to come ready.
1142 */
1143ASENTRY_NOPROFILE(Idle)
1144#if defined(LOCKDEBUG)
1145	/* Release sched_lock */
1146	jbsr	_C_LABEL(sched_unlock_idle)
1147#endif
1148	stop	#PSL_LOWIPL
1149	movw	#PSL_HIGHIPL,%sr
1150#if defined(LOCKDEBUG)
1151	/* Acquire sched_lock */
1152	jbsr	_C_LABEL(sched_lock_idle)
1153#endif
1154	movl	_C_LABEL(sched_whichqs),%d0
1155	jeq	_ASM_LABEL(Idle)
1156	jra	Lsw1
1157
1158Lbadsw:
1159	movl	#Lsw0,%sp@-
1160	jbsr	_C_LABEL(panic)
1161	/*NOTREACHED*/
1162
1163/*
1164 * Cpu_switch()
1165 *
1166 * NOTE: On the mc68851 (318/319/330) we attempt to avoid flushing the
1167 * entire ATC.  The effort involved in selective flushing may not be
1168 * worth it, maybe we should just flush the whole thing?
1169 *
1170 * NOTE 2: With the new VM layout we now no longer know if an inactive
1171 * user's PTEs have been changed (formerly denoted by the SPTECHG p_flag
1172 * bit).  For now, we just always flush the full ATC.
1173 */
1174ENTRY(cpu_switch)
1175	movl	_C_LABEL(curpcb),%a0	| current pcb
1176	movw	%sr,%a0@(PCB_PS)	| save sr before changing ipl
1177#ifdef notyet
1178	movl	_C_LABEL(curproc),%sp@-	| remember last proc running
1179#endif
1180	clrl	_C_LABEL(curproc)
1181
1182	/*
1183	 * Find the highest-priority queue that isn't empty,
1184	 * then take the first proc from that queue.
1185	 */
1186	movl	_C_LABEL(sched_whichqs),%d0
1187	jeq	_ASM_LABEL(Idle)
1188Lsw1:
1189	/*
1190	 * Interrupts are blocked, sched_lock is held.  If
1191	 * we come here via Idle, %d0 contains the contents
1192	 * of a non-zero sched_whichqs.
1193	 */
1194	movl	%d0,%d1
1195	negl	%d0
1196	andl	%d1,%d0
1197	bfffo	%d0{#0:#32},%d1
1198	eorib	#31,%d1
1199
1200	movl	%d1,%d0
1201	lslb	#3,%d1			| convert queue number to index
1202	addl	#_C_LABEL(sched_qs),%d1	| locate queue (q)
1203	movl	%d1,%a1
1204	movl	%a1@(P_FORW),%a0	| p = q->p_forw
1205	cmpal	%d1,%a0			| anyone on queue?
1206	jeq	Lbadsw			| no, panic
1207#ifdef DIAGNOSTIC
1208	tstl	%a0@(P_WCHAN)
1209	jne	Lbadsw
1210	cmpb	#SRUN,%a0@(P_STAT)
1211	jne	Lbadsw
1212#endif
1213	movl	%a0@(P_FORW),%a1@(P_FORW)	| q->p_forw = p->p_forw
1214	movl	%a0@(P_FORW),%a1		| n = p->p_forw
1215	movl	%a0@(P_BACK),%a1@(P_BACK)	| n->p_back = q
1216	cmpal	%d1,%a1			| anyone left on queue?
1217	jne	Lsw2			| yes, skip
1218	movl	_C_LABEL(sched_whichqs),%d1
1219	bclr	%d0,%d1			| no, clear bit
1220	movl	%d1,_C_LABEL(sched_whichqs)
1221Lsw2:
1222	/* p->p_cpu initialized in fork1() for single-processor */
1223	movb	#SONPROC,%a0@(P_STAT)		| p->p_stat = SONPROC
1224	movl	%a0,_C_LABEL(curproc)
1225	clrl	_C_LABEL(want_resched)
1226#ifdef notyet
1227	movl	%sp@+,%a1
1228	cmpl	%a0,%a1				| switching to same proc?
1229	jeq	Lswdone				| yes, skip save and restore
1230#endif
1231	/*
1232	 * Save state of previous process in its pcb.
1233	 */
1234	movl	_C_LABEL(curpcb),%a1
1235	moveml	%d2-%d7/%a2-%a7,%a1@(PCB_REGS)	| save non-scratch registers
1236	movl	%usp,%a2			| grab USP (a2 has been saved)
1237	movl	%a2,%a1@(PCB_USP)		| and save it
1238	movl	_C_LABEL(CMAP2),%a1@(PCB_CMAP2)	| save temporary map PTE
1239#ifdef FPCOPROC
1240#ifdef FPU_EMULATE
1241	tstl	_C_LABEL(fputype)		| do we have any FPU?
1242	jeq	Lswnofpsave			| no, dont save
1243#endif
1244	lea	%a1@(PCB_FPCTX),%a2		| pointer to FP save area
1245	fsave	%a2@				| save FP state
1246#if defined(M68020) || defined(M68030) || defined(M68040)
1247#ifdef M68060
1248	cmpl	#CPU_68060,_C_LABEL(cputype)
1249	jeq	Lsavfp60
1250#endif
1251	tstb	%a2@				| null state frame?
1252	jeq	Lswnofpsave			| yes, all done
1253	fmovem	%fp0-%fp7,%a2@(FPF_REGS)	| save FP general registers
1254	fmovem	%fpcr/%fpsr/%fpi,%a2@(FPF_FPCR)	| save FP control registers
1255#ifdef M68060
1256	jra	Lswnofpsave
1257#endif
1258#endif
1259#ifdef M68060
1260Lsavfp60:
1261	tstb	%a2@(2)				| null state frame?
1262	jeq	Lswnofpsave			| yes, all done
1263	fmovem	%fp0-%fp7,%a2@(FPF_REGS)	| save FP general registers
1264	fmovem	%fpcr,%a2@(FPF_FPCR)		| save FP control registers
1265	fmovem	%fpsr,%a2@(FPF_FPSR)
1266	fmovem	%fpi,%a2@(FPF_FPI)
1267#endif
1268Lswnofpsave:
1269#endif
1270
1271	clrl	%a0@(P_BACK)			| clear back link
1272	movl	%a0@(P_ADDR),%a1		| get p_addr
1273	movl	%a1,_C_LABEL(curpcb)
1274	movb	%a1@(PCB_FLAGS+1),_ASM_LABEL(pcbflag) | copy of pcb_flags low byte
1275
1276#if defined(LOCKDEBUG)
1277	/*
1278	 * Done mucking with the run queues, release the
1279	 * scheduler lock, but keep interrupts out.
1280	 */
1281	movl	%a0,sp@-			| not args...
1282	movl	%a1,sp@-			| ...just saving
1283	jbsr	_C_LABEL(sched_unlock_idle)
1284	movl	sp@+,%a1
1285	movl	sp@+,%a0
1286#endif
1287
1288	/*
1289	 * Activate process's address space.
1290	 * XXX Should remember the last USTP value loaded, and call this
1291	 * XXX only if it has changed.
1292	 */
1293	pea	%a0@				| push proc
1294	jbsr	_C_LABEL(pmap_activate)		| pmap_activate(p)
1295	addql	#4,%sp
1296	movl	_C_LABEL(curpcb),%a1		| restore p_addr
1297
1298	lea	_ASM_LABEL(tmpstk),%sp		| now goto a tmp stack for NMI
1299
1300	movl	%a1@(PCB_CMAP2),_C_LABEL(CMAP2)	| reload tmp map
1301	moveml	%a1@(PCB_REGS),%d2-%d7/%a2-%a7	| and registers
1302	movl	%a1@(PCB_USP),%a0
1303	movl	%a0,%usp			| and USP
1304#ifdef FPCOPROC
1305#ifdef FPU_EMULATE
1306	tstl	_C_LABEL(fputype)		| do we _have_ any fpu?
1307	jne	Lresnonofpatall
1308	movw	%a1@(PCB_PS),%sr		| no, restore PS
1309	moveq	#1,%d0				| return 1 (for alternate rets)
1310	rts
1311Lresnonofpatall:
1312#endif
1313	lea	%a1@(PCB_FPCTX),%a0		| pointer to FP save area
1314#if defined(M68020) || defined(M68030) || defined(M68040)
1315#ifdef M68060
1316	cmpl	#CPU_68060,_C_LABEL(cputype)
1317	jeq	Lresfp60rest1
1318#endif
1319	tstb	%a0@				| null state frame?
1320	jeq	Lresfprest2			| yes, easy
1321	fmovem	%a0@(FPF_FPCR),%fpcr/%fpsr/%fpi	| restore FP control registers
1322	fmovem	%a0@(FPF_REGS),%fp0-%fp7	| restore FP general registers
1323Lresfprest2:
1324	frestore %a0@				| restore state
1325	movw	%a1@(PCB_PS),%sr		| no, restore PS
1326	moveq	#1,%d0				| return 1 (for alternate rets)
1327	rts
1328#endif
1329
1330#ifdef M68060
1331Lresfp60rest1:
1332	tstb	%a0@(2)				| null state frame?
1333	jeq	Lresfp60rest2			| yes, easy
1334	fmovem	%a0@(FPF_FPCR),%fpcr		| restore FP control registers
1335	fmovem	%a0@(FPF_FPSR),%fpsr
1336	fmovem	%a0@(FPF_FPI),%fpi
1337	fmovem	%a0@(FPF_REGS),%fp0-%fp7	| restore FP general registers
1338Lresfp60rest2:
1339	frestore %a0@				| restore state
1340	movw	%a1@(PCB_PS),%sr		| no, restore PS
1341	moveq	#1,%d0				| return 1 (for alternate rets)
1342	rts
1343#endif
1344#endif
1345
1346/*
1347 * savectx(pcb)
1348 * Update pcb, saving current processor state
1349 */
1350ENTRY(savectx)
1351	movl	%sp@(4),%a1
1352	movw	%sr,%a1@(PCB_PS)
1353	movl	%usp,%a0			| grab USP
1354	movl	%a0,%a1@(PCB_USP)			| and save it
1355	moveml	%d2-%d7/%a2-%a7,%a1@(PCB_REGS)	| save non-scratch registers
1356	movl	_C_LABEL(CMAP2),%a1@(PCB_CMAP2)	| save temporary map PTE
1357#ifdef FPCOPROC
1358#ifdef FPU_EMULATE
1359	tstl	_C_LABEL(fputype)
1360	jeq	Lsavedone
1361#endif
1362	lea	%a1@(PCB_FPCTX),%a0		| pointer to FP save area
1363	fsave	%a0@				| save FP state
1364#if defined(M68020) || defined(M68030) || defined(M68040)
1365#ifdef M68060
1366	cmpl	#CPU_68060,_C_LABEL(cputype)
1367	jeq	Lsavctx60
1368#endif
1369	tstb	%a0@				| null state frame?
1370	jeq	Lsavedone			| yes, all done
1371	fmovem	%fp0-%fp7,%a0@(FPF_REGS)	| save FP general registers
1372	fmovem	%fpcr/%fpsr/%fpi,%a0@(FPF_FPCR)	| save FP control registers
1373#ifdef	M68060
1374	moveq	#0,%d0
1375	rts
1376#endif
1377#endif
1378#ifdef	M68060
1379Lsavctx60:
1380	tstb	%a0@(2)
1381	jeq	Lsavedone
1382	fmovem	%fp0-%fp7,%a0@(FPF_REGS)	| save FP general registers
1383	fmovem	%fpcr,%a0@(FPF_FPCR)		| save FP control registers
1384	fmovem	%fpsr,%a0@(FPF_FPSR)
1385	fmovem	%fpi,%a0@(FPF_FPI)
1386#endif
1387#endif
1388Lsavedone:
1389	moveq	#0,%d0				| return 0
1390	rts
1391
1392/*
1393 * Copy 1 relocation unit (NBPG bytes)
1394 * from user virtual address to physical address
1395 */
1396ENTRY(copyseg)
1397	movl	_C_LABEL(curpcb),%a1		| current pcb
1398	movl	#Lcpydone,%a1@(PCB_ONFAULT)	| where to return to on a fault
1399	movl	%sp@(8),%d0			| destination page number
1400	moveq	#PGSHIFT,%d1
1401	lsll	%d1,%d0				| convert to address
1402	orl	#PG_CI+PG_RW+PG_V,%d0		| make sure valid and writable
1403	movl	_C_LABEL(CMAP2),%a0
1404	movl	_C_LABEL(CADDR2),%sp@-		| destination kernel VA
1405	movl	%d0,%a0@			| load in page table
1406	jbsr	_ASM_LABEL(__TBIS)		| invalidate any old mapping
1407	addql	#4,%sp
1408	movl	_C_LABEL(CADDR2),%a1		| destination addr
1409	movl	%sp@(4),%a0			| source addr
1410	movl	#NBPG/4-1,%d0			| count
1411Lcpyloop:
1412	movsl	%a0@+,%d1			| read longword
1413	movl	%d1,%a1@+			| write longword
1414	dbf	%d0,Lcpyloop			| continue until done
1415Lcpydone:
1416	movl	_C_LABEL(curpcb),%a1		| current pcb
1417	clrl	%a1@(PCB_ONFAULT) 		| clear error catch
1418	rts
1419
1420/*
1421 * Invalidate entire TLB.
1422 */
1423ASLOCAL(__TBIA)
1424	cmpl	#MMU_68040,_C_LABEL(mmutype)
1425	jeq	Ltbia040
1426	tstl	_C_LABEL(mmutype)
1427	jpl	Lmc68851a			| 68851 implies no d-cache
1428	pflusha					| flush entire TLB
1429	movl	#DC_CLEAR,%d0
1430	movc	%d0,%cacr			| invalidate on-chip d-cache
1431	rts
1432Lmc68851a:
1433	pflusha
1434	rts
1435Ltbia040:
1436	.word	0xf518				| pflusha
1437#ifdef M68060
1438	cmpl	#CPU_68060,_C_LABEL(cputype)
1439	jne	Ltbiano60
1440	movc	%cacr,%d0
1441	orl	#IC60_CABC,%d0			| and clear all btc entries
1442	movc	%d0,%cacr
1443#endif
1444Ltbiano60:
1445	rts
1446
1447/*
1448 * Invalidate any TLB entry for given VA (TB Invalidate Single)
1449 */
1450ASLOCAL(__TBIS)
1451#ifdef DEBUG
1452	tstl	_ASM_LABEL(fulltflush)		| being conservative?
1453	jne	_ASM_LABEL(__TBIA)		| yes, flush entire TLB
1454#endif
1455	movl	%sp@(4),%a0			| get addr to flush
1456	cmpl	#MMU_68040,_C_LABEL(mmutype)
1457	jeq	Ltbis040
1458	tstl	_C_LABEL(mmutype)
1459	jpl	Lmc68851b			| is 68851?
1460	pflush	#0,#0,%a0@			| flush address from both sides
1461	movl	#DC_CLEAR,%d0
1462	movc	%d0,%cacr			| invalidate on-chip data cache
1463	rts
1464Lmc68851b:
1465	pflushs	#0,#0,%a0@			| flush address from both sides
1466	rts
1467Ltbis040:
1468	moveq	#FC_SUPERD,%d0			| select supervisor
1469	movc	%d0,%dfc
1470	.word	0xf508				| pflush a0@
1471	moveq	#FC_USERD,%d0			| select user
1472	movc	%d0,%dfc
1473	.word	0xf508				| pflush a0@
1474#ifdef M68060
1475	cmpl	#CPU_68060,_C_LABEL(cputype)
1476	jne	Ltbisno60
1477	movc	%cacr,%d0
1478	orl	#IC60_CABC,%d0			| and clear all btc entries
1479	movc	%d0,%cacr
1480Ltbisno60:
1481#endif
1482	rts
1483
1484ENTRY(ecacheon)
1485	rts
1486
1487ENTRY(ecacheoff)
1488	rts
1489
1490/*
1491 * Get callers current SP value.
1492 * Note that simply taking the address of a local variable in a C function
1493 * doesn't work because callee saved registers may be outside the stack frame
1494 * defined by A6 (e.g. GCC generated code).
1495 */
1496ENTRY(getsp)
1497	movl	%sp,%d0				| get current SP
1498	addql	#4,%d0				| compensate for return address
1499	movl	%d0,%a0				| Comply with ELF ABI
1500	rts
1501
1502ENTRY(getsfc)
1503	movc	%sfc,%d0
1504	rts
1505ENTRY(getdfc)
1506	movc	%dfc,%d0
1507	rts
1508
1509/*
1510 * Check out a virtual address to see if it's okay to write to.
1511 *
1512 * probeva(va, fc)
1513 *
1514 */
1515ENTRY(probeva)
1516	movl	%sp@(8),%d0
1517	movec	%d0,%dfc
1518	movl	%sp@(4),%a0
1519	.word	0xf548				| ptestw (a0)
1520	moveq	#FC_USERD,%d0			| restore DFC to user space
1521	movc	%d0,%dfc
1522	.word	0x4e7a,0x0805			| movec  MMUSR,d0
1523	rts
1524
1525/*
1526 * Load a new user segment table pointer.
1527 */
1528ENTRY(loadustp)
1529	movl	%sp@(4),%d0			| new USTP
1530	moveq	#PGSHIFT,%d1
1531	lsll	%d1,%d0				| convert to addr
1532#ifdef M68060
1533	cmpl	#CPU_68060,_C_LABEL(cputype)	| 68060?
1534	jeq	Lldustp060			|  yes, skip
1535#endif
1536	cmpl	#MMU_68040,_C_LABEL(mmutype)	| 68040?
1537	jeq	Lldustp040			|  yes, skip
1538	pflusha					| flush entire TLB
1539	lea	_C_LABEL(protorp),%a0		| CRP prototype
1540	movl	%d0,%a0@(4)			| stash USTP
1541	pmove	%a0@,%crp			| load root pointer
1542	movl	#CACHE_CLR,%d0
1543	movc	%d0,%cacr			| invalidate cache(s)
1544	rts
1545#ifdef M68060
1546Lldustp060:
1547	movc	%cacr,%d1
1548	orl	#IC60_CUBC,%d1			| clear user btc entries
1549	movc	%d1,%cacr
1550#endif
1551Lldustp040:
1552	.word	0xf518				| pflusha
1553	.word	0x4e7b,0x0806			| movec d0,URP
1554	rts
1555
1556/*
1557 * Flush any hardware context associated with given USTP.
1558 * Only does something for HP330 where we must flush RPT
1559 * and ATC entries in PMMU.
1560 */
1561ENTRY(flushustp)
1562#ifdef M68060
1563	cmpl	#CPU_68060,_C_LABEL(cputype)
1564	jeq	Lflustp060
1565#endif
1566	cmpl	#MMU_68040,_C_LABEL(mmutype)
1567	jeq	Lnot68851
1568	tstl	_C_LABEL(mmutype)		| 68851 PMMU?
1569	jle	Lnot68851			| no, nothing to do
1570	movl	%sp@(4),%d0			| get USTP to flush
1571	moveq	#PGSHIFT,%d1
1572	lsll	%d1,%d0				| convert to address
1573	movl	%d0,_C_LABEL(protorp)+4		| stash USTP
1574	pflushr	_C_LABEL(protorp)		| flush RPT/TLB entries
1575Lnot68851:
1576	rts
1577#ifdef M68060
1578Lflustp060:
1579	movc	%cacr,%d1
1580	orl	#IC60_CUBC,%d1			| clear user btc entries
1581	movc	%d1,%cacr
1582	rts
1583#endif
1584
1585
1586ENTRY(ploadw)
1587	movl	%sp@(4),%a0			| address to load
1588	cmpl	#MMU_68040,_C_LABEL(mmutype)
1589	jeq	Lploadw040
1590	ploadw	#1,%a0@				| pre-load translation
1591Lploadw040:					| should 68040 do a ptest?
1592	rts
1593
1594#ifdef FPCOPROC
1595/*
1596 * Save and restore 68881 state.
1597 * Pretty awful looking since our assembler does not
1598 * recognize FP mnemonics.
1599 */
1600ENTRY(m68881_save)
1601	movl	%sp@(4),%a0			| save area pointer
1602	fsave	%a0@				| save state
1603#if defined(M68020) || defined(M68030) || defined(M68040)
1604#ifdef M68060
1605	cmpl	#CPU_68060,_C_LABEL(cputype)
1606	jeq	Lm68060fpsave
1607#endif
1608	tstb	%a0@				| null state frame?
1609	jeq	Lm68881sdone			| yes, all done
1610	fmovem	%fp0-%fp7,%a0@(FPF_REGS)	| save FP general registers
1611	fmovem	%fpcr/%fpsr/%fpi,%a0@(FPF_FPCR)	| save FP control registers
1612Lm68881sdone:
1613	rts
1614#endif
1615
1616#ifdef M68060
1617Lm68060fpsave:
1618	tstb	%a0@(2)				| null state frame?
1619	jeq	Lm68060sdone			| yes, all done
1620	fmovem	%fp0-%fp7,%a0@(FPF_REGS)	| save FP general registers
1621	fmovem	%fpcr,%a0@(FPF_FPCR)		| save FP control registers
1622	fmovem	%fpsr,%a0@(FPF_FPSR)
1623	fmovem	%fpi,%a0@(FPF_FPI)
1624Lm68060sdone:
1625	rts
1626#endif
1627
1628ENTRY(m68881_restore)
1629	movl	%sp@(4),%a0			| save area pointer
1630#if defined(M68020) || defined(M68030) || defined(M68040)
1631#if defined(M68060)
1632	cmpl	#CPU_68060,_C_LABEL(cputype)
1633	jeq	Lm68060fprestore
1634#endif
1635	tstb	%a0@				| null state frame?
1636	jeq	Lm68881rdone			| yes, easy
1637	fmovem	%a0@(FPF_FPCR),%fpcr/%fpsr/%fpi	| restore FP control registers
1638	fmovem	%a0@(FPF_REGS),%fp0-%fp7	| restore FP general registers
1639Lm68881rdone:
1640	frestore %a0@				| restore state
1641	rts
1642#endif
1643
1644#ifdef M68060
1645Lm68060fprestore:
1646	tstb	%a0@(2)				| null state frame?
1647	jeq	Lm68060fprdone			| yes, easy
1648	fmovem	%a0@(FPF_FPCR),%fpcr		| restore FP control registers
1649	fmovem	%a0@(FPF_FPSR),%fpsr
1650	fmovem	%a0@(FPF_FPI),%fpi
1651	fmovem	%a0@(FPF_REGS),%fp0-%fp7	| restore FP general registers
1652Lm68060fprdone:
1653	frestore %a0@				| restore state
1654	rts
1655#endif
1656#endif
1657
1658/*
1659 * Handle the nitty-gritty of rebooting the machine.
1660 *
1661 */
1662#if defined(P5PPC68KBOARD)
1663	.data
1664GLOBAL(p5ppc)
1665	.long	0
1666	.text
1667#endif
1668
1669ENTRY_NOPROFILE(doboot)
1670	movl	#CACHE_OFF,%d0
1671	cmpl	#MMU_68040,_C_LABEL(mmutype)	| is it 68040
1672	jne	Ldoboot0
1673	.word	0xf4f8			| cpusha bc - push and invalidate caches
1674	nop
1675	movl	#CACHE40_OFF,%d0
1676Ldoboot0:
1677	movc	%d0,%cacr			| disable on-chip cache(s)
1678
1679	movw	#0x2700,%sr			| cut off any interrupts
1680
1681#if defined(P5PPC68KBOARD)
1682	tstl	_C_LABEL(p5ppc)
1683	jne	Lp5ppcboot
1684#endif
1685#if defined(DRACO)
1686	cmpb	#0x7d,_C_LABEL(machineid)
1687	jeq	LdbOnDraCo
1688#endif
1689
1690	| clear first 4k of CHIPMEM
1691	movl	_C_LABEL(CHIPMEMADDR),%a0
1692	movl	%a0,%a1
1693	movl	#1024,%d0
1694Ldb1:
1695	clrl	%a0@+
1696	dbra	%d0,Ldb1
1697
1698	| now, copy the following code over
1699|	lea	%a1@(Ldoreboot),%a0	| KVA starts at 0, CHIPMEM is phys 0
1700|	lea	%a1@(Ldorebootend),%a1
1701|	lea	%pc@(Ldoreboot-.+2),%a0
1702|	addl	%a1,%a0
1703|	lea	%a0@(128),%a1
1704|	lea	%pc@(Ldoreboot-.+2),%a2
1705	lea	Ldoreboot,%a2
1706	lea	Ldorebootend,%a0
1707	addl	%a1,%a0
1708	addl	%a2,%a1
1709	exg	%a0,%a1
1710Ldb2:
1711	movel	%a2@+,%a0@+
1712	cmpl	%a1,%a0
1713	jle	Ldb2
1714
1715	| ok, turn off MMU..
1716Ldoreboot:
1717	cmpl	#MMU_68040,_C_LABEL(mmutype)	| is it 68040
1718 	jeq	Lmmuoff040
1719	lea	_ASM_LABEL(zero),%a0
1720	pmove	%a0@,%tc		| Turn off MMU
1721	lea	_ASM_LABEL(nullrp),%a0
1722	pmove	%a0@,%crp		| Turn off MMU some more
1723	pmove	%a0@,%srp		| Really, really, turn off MMU
1724	jra	Ldoboot1
1725Lmmuoff040:
1726	movl	#0,%d0
1727	.word	0x4e7b,0x0003		| movc d0,TC
1728	.word	0x4e7b,0x0806		| movc d0,URP
1729	.word	0x4e7b,0x0807		| movc d0,SRP
1730Ldoboot1:
1731
1732	| this weird code is the OFFICIAL way to reboot an Amiga ! ..
1733	lea	0x1000000,%a0
1734	subl	%a0@(-0x14),%a0
1735	movl	%a0@(4),%a0
1736	subl	#2,%a0
1737	cmpw	#0x4e70,%a0@		| 68040 kludge: if ROM entry is not
1738	jne	Ldoreset		| a reset, do the reset here
1739	jmp	%a0@			| otherwise, jump to the ROM to reset
1740	| reset needs to be on longword boundary
1741	nop
1742#ifdef __ELF__
1743	.align	4
1744#else
1745	.align	2
1746#endif
1747Ldoreset:
1748	| reset unconfigures all memory!
1749	reset
1750	| now rely on prefetch for next jmp
1751	jmp	%a0@
1752	| NOT REACHED
1753
1754#if defined(P5PPC68KBOARD)
1755Lp5ppcboot:
1756| The Linux-Apus boot code does it in a similar way
1757| For 040 on uncached pages, eieio can be replaced by nothing.
1758	movl	_C_LABEL(ZTWOROMADDR),%a0
1759	lea	%a0@(0xf60000-0xd80000),%a0
1760	movb	#0x60,%a0@(0x20)
1761	movb	#0x50,%a0@(0x20)
1762	movb	#0x30,%a0@(0x20)
1763	movb	#0x40,%a0@(0x18)
1764	movb	#0x04,%a0@
1765Lwaithere:
1766	jra	Lwaithere
1767#endif
1768
1769#ifdef DRACO
1770LdbOnDraCo:
1771| we use a TTR. We want to boot even if half of us is already dead.
1772
1773	movl	_C_LABEL(boot_fphystart), %d0
1774	lea	LdoDraCoBoot, %a0
1775	lea	%a0@(%d0),%a0
1776	andl	#0xFF000000,%d0
1777	orl	#0x0000C044,%d0	| enable, supervisor, CI, RO
1778	.word	0x4e7b,0x0004	| movc d0,ITT0
1779	jmp	%a0@
1780
1781#ifdef __ELF__
1782	.align	4
1783#else
1784	.align	2
1785#endif
1786LdoDraCoBoot:
1787| turn off MMU now ... were more ore less guaranteed to run on 040/060:
1788	movl	#0,%d0
1789	.word	0x4e7b,0x0003	| movc d0,TC
1790	.word	0x4e7b,0x0806	| movc d0,URP
1791	.word	0x4e7b,0x0807	| movc d0,SRP
1792	.word	0x4e7b,0x0004	| movc d0,ITT0
1793	nop
1794| map in boot ROM @0:
1795	reset
1796| and simulate what a reset exception would have done.
1797	movl	4,%a0
1798	movl	0,%a7
1799	jmp	%a0@
1800	| NOT REACHED
1801#endif
1802/*
1803 * Reboot directly into a new kernel image.
1804 * kernel_reload(image, image_size, entry,
1805 *		 fastram_start, fastram_size, chipram_start, esym, eclockfreq)
1806 */
1807ENTRY_NOPROFILE(kernel_reload)
1808	lea	Lreload_copy,%a0	| cursory validity check of new kernel
1809	movl	%a0@,%d0		|  to see if the kernel reload code
1810	addl	%sp@(4),%a0		|  in new image matches running kernel
1811	cmpl	%a0@,%d0
1812	jeq	Lreload_ok
1813	rts				| It doesn't match - can't reload
1814Lreload_ok:
1815	jsr	_C_LABEL(bootsync)
1816	CUSTOMADDR(%a5)
1817
1818	movew	#(1<<9),%a5@(0x096)	| disable DMA (before clobbering chipmem)
1819
1820	movl	#CACHE_OFF,%d0
1821	cmpl	#MMU_68040,_C_LABEL(mmutype)
1822	jne	Lreload1
1823	.word	0xf4f8		| cpusha bc - push and invalidate caches
1824	nop
1825	movl	#CACHE40_OFF,%d0
1826Lreload1:
1827	movc	%d0,%cacr		| disable on-chip cache(s)
1828
1829	movw	#0x2700,%sr		| cut off any interrupts
1830	movel	_C_LABEL(boothowto),%d7	| save boothowto
1831	movel	_C_LABEL(machineid),%d5	| (and machineid)
1832
1833	movel	%sp@(16),%a0		| load memory parameters
1834	movel	%sp@(20),%d0
1835	movel	%sp@(24),%d1
1836	movel	%sp@(28),%a4		| esym
1837	movel	%sp@(32),%d4		| eclockfreq
1838	movel	%sp@(36),%d3		| AGA mode
1839	movel	%sp@(40),%a2		| sync inhibit flags
1840	movel	%sp@(44),%d6		| boot partition offset
1841
1842	movel	%sp@(12),%a6		| find entrypoint (a6)
1843
1844	movel	%sp@(4),%a1		| copy kernel to low chip memory
1845	movel	%sp@(8),%d2
1846	movl	_C_LABEL(CHIPMEMADDR),%a3
1847Lreload_copy:
1848	movel	%a1@+,%a3@+
1849	subl	#4,%d2
1850	jcc	Lreload_copy
1851
1852	| ok, turn off MMU..
1853	cmpl	#MMU_68040,_C_LABEL(mmutype)
1854	jeq	Lreload040
1855	lea	_ASM_LABEL(zero),%a3
1856	pmove	%a3@,%tc		| Turn off MMU
1857	lea	_ASM_LABEL(nullrp),%a3
1858	pmove	%a3@,%crp		| Turn off MMU some more
1859	pmove	%a3@,%srp		| Really, really, turn off MMU
1860	jra	Lreload2
1861Lreload040:
1862	movl	#0,%d2
1863	.word	0x4e7b,0x2003	| movc d2,TC
1864	.word	0x4e7b,0x2806	| movc d2,URP
1865	.word	0x4e7b,0x2807	| movc d2,SRP
1866Lreload2:
1867
1868	moveq	#0,%d2			| clear unused registers
1869	subl	%a1,%a1
1870	subl	%a3,%a3
1871	subl	%a5,%a5
1872	jmp	%a6@			| start new kernel
1873
1874
1875| A do-nothing MMU root pointer (includes the following long as well)
1876
1877ASLOCAL(nullrp)
1878	.long	0x7fff0001
1879ASLOCAL(zero)
1880	.long	0
1881Ldorebootend:
1882
1883#ifdef __ELF__
1884	.align 4
1885#else
1886	.align 2
1887#endif
1888	nop
1889ENTRY_NOPROFILE(delay)
1890ENTRY_NOPROFILE(DELAY)
1891	movql #10,%d1		| 2 +2
1892	movl %sp@(4),%d0	| 4 +4
1893	lsll %d1,%d0		| 8 +2
1894	movl _C_LABEL(delaydivisor),%d1	| A +6
1895Ldelay:				| longword aligned again.
1896	subl %d1,%d0
1897	jcc Ldelay
1898	rts
1899
1900#ifdef M68060
1901ENTRY_NOPROFILE(intemu60)
1902	addql	#1,L60iem
1903	jra	_C_LABEL(I_CALL_TOP)+128+0x00
1904ENTRY_NOPROFILE(fpiemu60)
1905	addql	#1,L60fpiem
1906	jra	_C_LABEL(FP_CALL_TOP)+128+0x30
1907ENTRY_NOPROFILE(fpdemu60)
1908	addql	#1,L60fpdem
1909	jra	_C_LABEL(FP_CALL_TOP)+128+0x38
1910ENTRY_NOPROFILE(fpeaemu60)
1911	addql	#1,L60fpeaem
1912	jra	_C_LABEL(FP_CALL_TOP)+128+0x40
1913#endif
1914
1915	.data
1916	.space	NBPG
1917ASLOCAL(tmpstk)
1918
1919GLOBAL(mmutype)
1920	.long	MMU_68851
1921GLOBAL(cputype)
1922	.long	CPU_68020
1923GLOBAL(ectype)
1924	.long	EC_NONE
1925GLOBAL(fputype)
1926	.long	FPU_NONE
1927GLOBAL(protorp)
1928	.long	0x80000002,0	| prototype root pointer
1929
1930GLOBAL(proc0paddr)
1931	.long	0		| KVA of proc0 u-area
1932
1933GLOBAL(delaydivisor)
1934	.long	12		| should be enough for 80 MHz 68060
1935				| will be adapted to other CPUs in
1936				| start_c_cleanup and calibrated
1937				| at clock attach time.
1938#ifdef DEBUG
1939ASGLOBAL(fulltflush)
1940	.long	0
1941ASGLOBAL(fullcflush)
1942	.long	0
1943ASGLOBAL(timebomb)
1944	.long	0
1945#endif
1946/* interrupt counters */
1947GLOBAL(intrnames)
1948	.asciz	"spur"		| spurious interrupt
1949	.asciz	"tbe/soft"	| serial TBE & software
1950	.asciz	"kbd/ports"	| keyboard & PORTS
1951	.asciz	"vbl"		| vertical blank
1952	.asciz	"audio"		| audio channels
1953	.asciz	"rbf"		| serial receive
1954	.asciz	"exter"		| EXTERN
1955	.asciz	"nmi"		| non-maskable
1956	.asciz	"clock"		| clock interrupts
1957	.asciz	"spur6"		| spurious level 6
1958#ifdef DRACO
1959	.asciz	"kbd/soft"	| 1: native keyboard, soft ints
1960	.asciz	"cia/zbus"	| 2: cia, PORTS
1961	.asciz	"lclbus"	| 3: local bus, e.g. Altais vbl
1962	.asciz	"drscsi"	| 4: mainboard scsi
1963	.asciz	"superio"	| 5: superio chip
1964	.asciz	"lcl/zbus"	| 6: lcl/zorro lev6
1965	.asciz	"buserr"	| 7: nmi: bus timeout
1966#endif
1967#ifdef M68060
1968	.asciz	"60intemu"
1969	.asciz	"60fpiemu"
1970	.asciz	"60fpdemu"
1971	.asciz	"60fpeaemu"
1972	.asciz	"60bpe"
1973#endif
1974#ifdef FPU_EMULATE
1975	.asciz	"fpe"
1976#endif
1977GLOBAL(eintrnames)
1978#ifdef __ELF__
1979	.align	4
1980#else
1981	.align	2
1982#endif
1983GLOBAL(intrcnt)
1984	.long	0,0,0,0,0,0,0,0,0,0
1985#ifdef DRACO
1986ASLOCAL(Drintrcnt)
1987	.long	0,0,0,0,0,0,0
1988#endif
1989#ifdef M68060
1990L60iem:		.long	0
1991L60fpiem:	.long	0
1992L60fpdem:	.long	0
1993L60fpeaem:	.long	0
1994L60bpe:		.long	0
1995#endif
1996#ifdef FPU_EMULATE
1997Lfpecnt:	.long	0
1998#endif
1999GLOBAL(eintrcnt)
2000