xref: /netbsd-src/sys/arch/mvme68k/mvme68k/locore.s (revision fdecd6a253f999ae92b139670d9e15cc9df4497c)
1/*	$NetBSD: locore.s,v 1.23 1997/05/13 18:01:13 gwr Exp $	*/
2
3/*
4 * Copyright (c) 1988 University of Utah.
5 * Copyright (c) 1980, 1990, 1993
6 *	The Regents of the University of California.  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.66 92/12/22$
41 *
42 *	@(#)locore.s	8.6 (Berkeley) 5/27/94
43 */
44
45#include "assym.h"
46#include <machine/asm.h>
47#include <machine/trap.h>
48
49/*
50 * Temporary stack for a variety of purposes.
51 * Try and make this the first thing is the data segment so it
52 * is page aligned.  Note that if we overflow here, we run into
53 * our text segment.
54 */
55	.data
56	.space	NBPG
57tmpstk:
58
59#define	RELOC(var, ar) \
60	lea	var,ar
61
62#define	CALLBUG(func)	\
63	trap #15; .short func
64
65/*
66 * Initialization
67 *
68 * The bootstrap loader loads us in starting at 0, and VBR is non-zero.
69 * On entry, args on stack are boot device, boot filename, console unit,
70 * boot flags (howto), boot device name, filesystem type name.
71 */
72	.comm	_lowram,4
73	.comm	_esym,4
74
75	.text
76	.globl	_edata
77	.globl	_etext,_end
78	.globl	start,_kernel_text
79| This is for kvm_mkdb, and should be the address of the beginning
80| of the kernel text segment (not necessarily the same as kernbase).
81_kernel_text:
82start:					| start of kernel and .text!
83	movw	#PSL_HIGHIPL,sr		| no interrupts
84	movl	#0,a5			| RAM starts at 0 (a5)
85	movl	sp@(4), d7		| get boothowto
86	movl	sp@(8), d6		| get bootaddr
87	movl	sp@(12),d5		| get bootctrllun
88	movl	sp@(16),d4		| get bootdevlun
89	movl	sp@(20),d3		| get bootpart
90	movl	sp@(24),d2		| get esyms
91
92	RELOC(_bootpart,a0)
93	movl	d3, a0@			| save bootpart
94	RELOC(_bootdevlun,a0)
95	movl	d4, a0@			| save bootdevlun
96	RELOC(_bootctrllun,a0)
97	movl	d5, a0@			| save booctrllun
98	RELOC(_bootaddr,a0)
99	movl	d6, a0@			| save bootaddr
100	RELOC(_boothowto,a0)
101	movl	d7, a0@			| save boothowto
102	/* note: d3-d7 free, d2 still in use */
103
104	RELOC(tmpstk, a0)
105	movl	a0,sp			| give ourselves a temporary stack
106
107	RELOC(_edata,a0)		| clear out BSS
108	movl	#_end-4,d0		| (must be <= 256 kB)
109	subl	#_edata,d0
110	lsrl	#2,d0
1111:	clrl	a0@+
112	dbra	d0,1b
113
114	RELOC(_esym, a0)
115	movl	d2,a0@			| store end of symbol table
116	/* d2 now free */
117	RELOC(_lowram, a0)
118	movl	a5,a0@			| store start of physical memory
119
120	movl	#CACHE_OFF,d0
121	movc	d0,cacr			| clear and disable on-chip cache(s)
122
123	/* ask the Bug what we are... */
124	clrl	sp@-
125	CALLBUG(MVMEPROM_GETBRDID)
126	movl	sp@+,a1
127
128	/* copy to a struct mvmeprom_brdid */
129	movl	#MVMEPROM_BRDID_SIZE,d0
130	RELOC(_boardid,a0)
1311:	movb	a1@+,a0@+
132	subql	#1,d0
133	bne	1b
134
135	/*
136	 * Grab the model number from _boardid and use the value
137	 * to setup machineid, cputype, and mmutype.
138	 */
139	clrl	d0
140	RELOC(_boardid,a1)
141	movw	a1@(MVMEPROM_BRDID_MODEL_OFFSET),d0
142	RELOC(_machineid,a0)
143	movl	d0,a0@
144
145#ifdef MVME147
146	/* MVME-147 - 68030 CPU/MMU */
147	cmpw	#MVME_147,d0
148	jne	Lnot147
149	RELOC(_mmutype,a0)
150	movl	#MMU_68030,a0@
151	RELOC(_cputype,a0)
152	movl	#CPU_68030,a0@
153
154	/* XXXCDC SHUTUP 147 CALL */
155	movb	#0, 0xfffe1026		| serial interrupt off
156	movb	#0, 0xfffe1018		| timer 1 off
157	movb	#0, 0xfffe1028		| ethernet off
158	/* XXXCDC SHUTUP 147 CALL */
159
160	/* Save our ethernet address */
161	RELOC(_myea, a0)
162	movl	0xfffe0778,a0@		| XXXCDC -- HARDWIRED HEX
163
164	/* initialize memory sizes (for pmap_bootstrap) */
165	movl	0xfffe0774,d1		| XXXCDC -- hardwired HEX
166	moveq	#PGSHIFT,d2
167	lsrl	d2,d1			| convert to page (click) number
168	RELOC(_maxmem, a0)
169	movl	d1,a0@			| save as maxmem
170	movl	a5,d0			| lowram value from ROM via boot
171	lsrl	d2,d0			| convert to page number
172	subl	d0,d1			| compute amount of RAM present
173	RELOC(_physmem, a0)
174	movl	d1,a0@			| and physmem
175
176	jra	Lstart1
177Lnot147:
178#endif
179
180#ifdef MVME162
181	/* MVME-162 - 68040 CPU/MMU */
182	cmpw	#MVME_162,d0
183	jne	Lnot162
184	RELOC(_mmutype,a0)
185	movl	#MMU_68040,a0@
186	RELOC(_cputype,a0)
187	movl	#CPU_68040,a0@
188#if 1	/* XXX */
189	jra	Lnotyet
190#else
191	/* XXX more XXX */
192	jra	Lstart1
193#endif
194Lnot162:
195#endif
196
197#ifdef MVME167
198	/* MVME-167 (also 166) - 68040 CPU/MMU */
199	cmpw	#MVME_166,d0
200	jeq	Lis167
201	cmpw	#MVME_167,d0
202	jne	Lnot167
203Lis167:
204	RELOC(_mmutype,a0)
205	movl	#MMU_68040,a0@
206	RELOC(_cputype,a0)
207	movl	#CPU_68040,a0@
208#if 1	/* XXX */
209	jra	Lnotyet
210#else
211	/* XXX more XXX */
212	jra	Lstart1
213#endif
214Lnot167:
215#endif
216
217#ifdef MVME177
218	/* MVME-177 (what about 172??) - 68060 CPU/MMU */
219	cmpw	#MVME_177,d0
220	jne	Lnot177
221	RELOC(_mmutype,a0)
222	movl	#MMU_68060,a0@
223	RELOC(_cputype,a0)
224	movl	#CPU_68060,a0@
225#if 1
226	jra	Lnotyet
227#else
228	/* XXX more XXX */
229	jra	Lstart1
230#endif
231Lnot177:
232#endif
233
234	/*
235	 * If we fall to here, the board is not supported.
236	 * Print a warning, then drop out to the Bug.
237	 */
238	.data
239Lnotconf:
240	.ascii	"Sorry, the kernel isn't configured for this model."
241Lenotconf:
242
243	.even
244	.text
245	movl	#Lenotconf,sp@-
246	movl	#Lnotconf,sp@-
247	CALLBUG(MVMEPROM_OUTSTRCRLF)
248	addql	#8,sp			| clean up stack after call
249
250	CALLBUG(MVMEPROM_EXIT)
251	/* NOTREACHED */
252
253Lnotyet:
254	/*
255	 * If we get here, it means a particular model
256	 * doesn't have the necessary support code in the
257	 * kernel.  Print a warning, then drop out to the Bug.
258	 */
259	.data
260Lnotsupp:
261	.ascii	"Sorry, NetBSD doesn't support this model yet."
262Lenotsupp:
263
264	.even
265	.text
266	movl	#Lenotsupp,sp@-
267	movl	#Lnotsupp,sp@-
268	CALLBUG(MVMEPROM_OUTSTRCRLF)
269	addql	#8,sp			| clean up stack after call
270
271	CALLBUG(MVMEPROM_EXIT)
272	/* NOTREACHED */
273
274Lstart1:
275/* initialize source/destination control registers for movs */
276	moveq	#FC_USERD,d0		| user space
277	movc	d0,sfc			|   as source
278	movc	d0,dfc			|   and destination of transfers
279/* configure kernel and proc0 VA space so we can get going */
280	.globl	_Sysseg, _pmap_bootstrap, _avail_start
281#ifdef DDB
282	RELOC(_esym,a0)			| end of static kernel test/data/syms
283	movl	a0@,d2
284	jne	Lstart2
285#endif
286	movl	#_end,d2		| end of static kernel text/data
287Lstart2:
288	addl	#NBPG-1,d2
289	andl	#PG_FRAME,d2		| round to a page
290	movl	d2,a4
291	addl	a5,a4			| convert to PA
292	movl	#0, sp@-		| firstpa
293	pea	a4@			| nextpa
294	RELOC(_pmap_bootstrap,a0)
295	jbsr	a0@			| pmap_bootstrap(firstpa, nextpa)
296	addql	#8,sp
297
298/*
299 * Enable the MMU.
300 * Since the kernel is mapped logical == physical, we just turn it on.
301 */
302	RELOC(_Sysseg, a0)		| system segment table addr
303	movl	a0@,d1			| read value (a KVA)
304	addl	a5,d1			| convert to PA
305	RELOC(_mmutype, a0)
306	cmpl	#MMU_68040,a0@		| 68040?
307	jne	Lmotommu1		| no, skip
308	.long	0x4e7b1807		| movc d1,srp
309	jra	Lstploaddone
310Lmotommu1:
311	RELOC(_protorp, a0)
312	movl	#0x80000202,a0@		| nolimit + share global + 4 byte PTEs
313	movl	d1,a0@(4)		| + segtable address
314	pmove	a0@,srp			| load the supervisor root pointer
315	movl	#0x80000002,a0@		| reinit upper half for CRP loads
316Lstploaddone:
317	RELOC(_mmutype, a0)
318	cmpl	#MMU_68040,a0@		| 68040?
319	jne	Lmotommu2		| no, skip
320	moveq	#0,d0			| ensure TT regs are disabled
321	.long	0x4e7b0004		| movc d0,itt0
322	.long	0x4e7b0005		| movc d0,itt1
323	.long	0x4e7b0006		| movc d0,dtt0
324	.long	0x4e7b0007		| movc d0,dtt1
325	.word	0xf4d8			| cinva bc
326	.word	0xf518			| pflusha
327	movl	#0x8000,d0
328	.long	0x4e7b0003		| movc d0,tc
329	movl	#0x80008000,d0
330	movc	d0,cacr			| turn on both caches
331	jmp	Lenab1
332Lmotommu2:
333	RELOC(_prototc, a2)
334	movl	#0x82c0aa00,a2@		| value to load TC with
335	pmove	a2@,tc			| load it
336Lenab1:
337
338/*
339 * Should be running mapped from this point on
340 */
341/* select the software page size now */
342	lea	tmpstk,sp		| temporary stack
343	jbsr	_vm_set_page_size	| select software page size
344/* set kernel stack, user SP, and initial pcb */
345	movl	_proc0paddr,a1		| get proc0 pcb addr
346	lea	a1@(USPACE-4),sp	| set kernel stack to end of area
347	movl	#USRSTACK-4,a2
348	movl	a2,usp			| init user SP
349	movl	a1,_curpcb		| proc0 is running
350#ifdef FPCOPROC
351	clrl	a1@(PCB_FPCTX)		| ensure null FP context
352	movl	a1,sp@-
353	jbsr	_m68881_restore		| restore it (does not kill a1)
354	addql	#4,sp
355#endif
356/* flush TLB and turn on caches */
357	jbsr	_TBIA			| invalidate TLB
358	cmpl	#MMU_68040,_mmutype	| 68040?
359	jeq	Lnocache0		| yes, cache already on
360	movl	#CACHE_ON,d0
361	movc	d0,cacr			| clear cache(s)
362Lnocache0:
363/* final setup for C code */
364	movl	#_vectab,d0		| set VBR
365	movc	d0,vbr
366	jbsr	_isrinit		| be ready for stray ints
367	jbsr	_mvme68k_init		| early model-dependent init
368	movw	#PSL_LOWIPL,sr		| lower SPL
369
370/*
371 * Create a fake exception frame so that cpu_fork() can copy it.
372 * main() nevers returns; we exit to user mode from a forked process
373 * later on.
374 */
375	clrw	sp@-			| vector offset/frame type
376	clrl	sp@-			| PC - filled in by "execve"
377	movw	#PSL_USER,sp@-		| in user mode
378	clrl	sp@-			| stack adjust count and padding
379	lea	sp@(-64),sp		| construct space for D0-D7/A0-A7
380	lea	_proc0,a0		| save pointer to frame
381	movl	sp,a0@(P_MD_REGS)	|   in proc0.p_md.md_regs
382
383	jra	_main			| main()
384
385	.globl _proc_trampoline
386_proc_trampoline:
387	movl	a3@(P_MD_REGS),sp	| process' frame pointer in sp
388	movl    a3,sp@-
389	jbsr    a2@
390	addql   #4,sp
391	movl    sp@(FR_SP),a0           | grab and load
392	movl    a0,usp                  |   user SP
393	moveml  sp@+,#0x7FFF            | restore most user regs
394	addql   #8,sp                   | toss SP and stack adjust
395	jra     rei                     | and return
396
397/*
398 * Use common m68k sigcode.
399 */
400#include <m68k/m68k/sigcode.s>
401
402/*
403 * Trap/interrupt vector routines
404 */
405#include <m68k/m68k/trap_subr.s>
406
407	.text
408	.globl	_trap, _nofault, _longjmp
409_buserr:
410	tstl	_nofault		| device probe?
411	jeq	Lberr			| no, handle as usual
412	movl	_nofault,sp@-		| yes,
413	jbsr	_longjmp		|  longjmp(nofault)
414Lberr:
415#if defined(M68040)
416	cmpl	#MMU_68040,_mmutype	| 68040?
417	jne	_addrerr		| no, skip
418	clrl	sp@-			| stack adjust count
419	moveml	#0xFFFF,sp@-		| save user registers
420	movl	usp,a0			| save the user SP
421	movl	a0,sp@(FR_SP)		|   in the savearea
422	lea	sp@(FR_HW),a1		| grab base of HW berr frame
423	moveq	#0,d0
424	movw	a1@(12),d0		| grab SSW
425	movl	a1@(20),d1		| and fault VA
426	btst	#11,d0			| check for mis-aligned access
427	jeq	Lberr2			| no, skip
428	addl	#3,d1			| yes, get into next page
429	andl	#PG_FRAME,d1		| and truncate
430Lberr2:
431	movl	d1,sp@-			| push fault VA
432	movl	d0,sp@-			| and padded SSW
433	btst	#10,d0			| ATC bit set?
434	jeq	Lisberr			| no, must be a real bus error
435	movc	dfc,d1			| yes, get MMU fault
436	movc	d0,dfc			| store faulting function code
437	movl	sp@(4),a0		| get faulting address
438	.word	0xf568			| ptestr a0@
439	movc	d1,dfc
440	.long	0x4e7a0805		| movc mmusr,d0
441	movw	d0,sp@			| save (ONLY LOW 16 BITS!)
442	jra	Lismerr
443#endif
444_addrerr:
445	clrl	sp@-			| stack adjust count
446	moveml	#0xFFFF,sp@-		| save user registers
447	movl	usp,a0			| save the user SP
448	movl	a0,sp@(FR_SP)		|   in the savearea
449	lea	sp@(FR_HW),a1		| grab base of HW berr frame
450#if defined(M68040)
451	cmpl	#MMU_68040,_mmutype	| 68040?
452	jne	Lbenot040		| no, skip
453	movl	a1@(8),sp@-		| yes, push fault address
454	clrl	sp@-			| no SSW for address fault
455	jra	Lisaerr			| go deal with it
456Lbenot040:
457#endif
458	moveq	#0,d0
459	movw	a1@(10),d0		| grab SSW for fault processing
460	btst	#12,d0			| RB set?
461	jeq	LbeX0			| no, test RC
462	bset	#14,d0			| yes, must set FB
463	movw	d0,a1@(10)		| for hardware too
464LbeX0:
465	btst	#13,d0			| RC set?
466	jeq	LbeX1			| no, skip
467	bset	#15,d0			| yes, must set FC
468	movw	d0,a1@(10)		| for hardware too
469LbeX1:
470	btst	#8,d0			| data fault?
471	jeq	Lbe0			| no, check for hard cases
472	movl	a1@(16),d1		| fault address is as given in frame
473	jra	Lbe10			| thats it
474Lbe0:
475	btst	#4,a1@(6)		| long (type B) stack frame?
476	jne	Lbe4			| yes, go handle
477	movl	a1@(2),d1		| no, can use save PC
478	btst	#14,d0			| FB set?
479	jeq	Lbe3			| no, try FC
480	addql	#4,d1			| yes, adjust address
481	jra	Lbe10			| done
482Lbe3:
483	btst	#15,d0			| FC set?
484	jeq	Lbe10			| no, done
485	addql	#2,d1			| yes, adjust address
486	jra	Lbe10			| done
487Lbe4:
488	movl	a1@(36),d1		| long format, use stage B address
489	btst	#15,d0			| FC set?
490	jeq	Lbe10			| no, all done
491	subql	#2,d1			| yes, adjust address
492Lbe10:
493	movl	d1,sp@-			| push fault VA
494	movl	d0,sp@-			| and padded SSW
495	movw	a1@(6),d0		| get frame format/vector offset
496	andw	#0x0FFF,d0		| clear out frame format
497	cmpw	#12,d0			| address error vector?
498	jeq	Lisaerr			| yes, go to it
499	movl	d1,a0			| fault address
500	movl	sp@,d0			| function code from ssw
501	btst	#8,d0			| data fault?
502	jne	Lbe10a
503	movql	#1,d0			| user program access FC
504					| (we dont seperate data/program)
505	btst	#5,a1@			| supervisor mode?
506	jeq	Lbe10a			| if no, done
507	movql	#5,d0			| else supervisor program access
508Lbe10a:
509	ptestr	d0,a0@,#7		| do a table search
510	pmove	psr,sp@			| save result
511	movb	sp@,d1
512	btst	#2,d1			| invalid (incl. limit viol. and berr)?
513	jeq	Lmightnotbemerr		| no -> wp check
514	btst	#7,d1			| is it MMU table berr?
515	jeq	Lismerr			| no, must be fast
516	jra	Lisberr1		| real bus err needs not be fast.
517Lmightnotbemerr:
518	btst	#3,d1			| write protect bit set?
519	jeq	Lisberr1		| no: must be bus error
520	movl	sp@,d0			| ssw into low word of d0
521	andw	#0xc0,d0		| Write protect is set on page:
522	cmpw	#0x40,d0		| was it read cycle?
523	jeq	Lisberr1		| yes, was not WPE, must be bus err
524Lismerr:
525	movl	#T_MMUFLT,sp@-		| show that we are an MMU fault
526	jra	_ASM_LABEL(faultstkadj)	| and deal with it
527Lisaerr:
528	movl	#T_ADDRERR,sp@-		| mark address error
529	jra	_ASM_LABEL(faultstkadj)	| and deal with it
530Lisberr1:
531	clrw	sp@			| re-clear pad word
532Lisberr:
533	movl	#T_BUSERR,sp@-		| mark bus error
534	jra	_ASM_LABEL(faultstkadj)	| and deal with it
535
536/*
537 * FP exceptions.
538 */
539_fpfline:
540#if defined(M68040)
541	cmpw	#0x202c,sp@(6)		| format type 2?
542	jne	_illinst		| no, not an FP emulation
543#ifdef FPSP
544	.globl	fpsp_unimp
545	jmp	fpsp_unimp		| yes, go handle it
546#else
547	clrl	sp@-			| stack adjust count
548	moveml	#0xFFFF,sp@-		| save registers
549	moveq	#T_FPEMULI,d0		| denote as FP emulation trap
550	jra	fault			| do it
551#endif
552#else
553	jra	_illinst
554#endif
555
556_fpunsupp:
557#if defined(M68040)
558	cmpl	#MMU_68040,_mmutype	| 68040?
559	jne	_illinst		| no, treat as illinst
560#ifdef FPSP
561	.globl	fpsp_unsupp
562	jmp	fpsp_unsupp		| yes, go handle it
563#else
564	clrl	sp@-			| stack adjust count
565	moveml	#0xFFFF,sp@-		| save registers
566	moveq	#T_FPEMULD,d0		| denote as FP emulation trap
567	jra	fault			| do it
568#endif
569#else
570	jra	_illinst
571#endif
572
573/*
574 * Handles all other FP coprocessor exceptions.
575 * Note that since some FP exceptions generate mid-instruction frames
576 * and may cause signal delivery, we need to test for stack adjustment
577 * after the trap call.
578 */
579	.globl	_fpfault
580_fpfault:
581#ifdef FPCOPROC
582	clrl	sp@-		| stack adjust count
583	moveml	#0xFFFF,sp@-	| save user registers
584	movl	usp,a0		| and save
585	movl	a0,sp@(FR_SP)	|   the user stack pointer
586	clrl	sp@-		| no VA arg
587	movl	_curpcb,a0	| current pcb
588	lea	a0@(PCB_FPCTX),a0 | address of FP savearea
589	fsave	a0@		| save state
590	tstb	a0@		| null state frame?
591	jeq	Lfptnull	| yes, safe
592	clrw	d0		| no, need to tweak BIU
593	movb	a0@(1),d0	| get frame size
594	bset	#3,a0@(0,d0:w)	| set exc_pend bit of BIU
595Lfptnull:
596	fmovem	fpsr,sp@-	| push fpsr as code argument
597	frestore a0@		| restore state
598	movl	#T_FPERR,sp@-	| push type arg
599	jra	_ASM_LABEL(faultstkadj) | call trap and deal with stack cleanup
600#else
601	jra	_badtrap	| treat as an unexpected trap
602#endif
603
604/*
605 * Other exceptions only cause four and six word stack frame and require
606 * no post-trap stack adjustment.
607 */
608
609	.globl	_straytrap
610_badtrap:
611	moveml	#0xC0C0,sp@-		| save scratch regs
612	movw	sp@(22),sp@-		| push exception vector info
613	clrw	sp@-
614	movl	sp@(22),sp@-		| and PC
615	jbsr	_straytrap		| report
616	addql	#8,sp			| pop args
617	moveml	sp@+,#0x0303		| restore regs
618	jra	rei			| all done
619
620	.globl	_syscall
621_trap0:
622	clrl	sp@-			| stack adjust count
623	moveml	#0xFFFF,sp@-		| save user registers
624	movl	usp,a0			| save the user SP
625	movl	a0,sp@(FR_SP)		|   in the savearea
626	movl	d0,sp@-			| push syscall number
627	jbsr	_syscall		| handle it
628	addql	#4,sp			| pop syscall arg
629	tstl	_astpending
630	jne	Lrei2
631	tstb	_ssir
632	jeq	Ltrap1
633	movw	#SPL1,sr
634	tstb	_ssir
635	jne	Lsir1
636Ltrap1:
637	movl	sp@(FR_SP),a0		| grab and restore
638	movl	a0,usp			|   user SP
639	moveml	sp@+,#0x7FFF		| restore most registers
640	addql	#8,sp			| pop SP and stack adjust
641	rte
642
643/*
644 * Routines for traps 1 and 2.  The meaning of the two traps depends
645 * on whether we are an HPUX compatible process or a native 4.3 process.
646 * Our native 4.3 implementation uses trap 1 as sigreturn() and trap 2
647 * as a breakpoint trap.  HPUX uses trap 1 for a breakpoint, so we have
648 * to make adjustments so that trap 2 is used for sigreturn.
649 */
650_trap1:
651#ifdef COMPAT_HPUX
652	btst	#MDP_TRCB,mdpflag	| being traced by an HPUX process?
653	jeq	sigreturn		| no, trap1 is sigreturn
654	jra	_trace			| yes, trap1 is breakpoint
655#else
656	jra	sigreturn		| no, trap1 is sigreturn
657#endif
658
659_trap2:
660#ifdef COMPAT_HPUX
661	btst	#MDP_TRCB,mdpflag	| being traced by an HPUX process?
662	jeq	_trace			| no, trap2 is breakpoint
663	jra	sigreturn		| yes, trap2 is sigreturn
664#else
665	jra	_trace			| no, trap2 is breakpoint
666#endif
667
668/*
669 * Trap 12 is the entry point for the cachectl "syscall" (both HPUX & BSD)
670 *	cachectl(command, addr, length)
671 * command in d0, addr in a1, length in d1
672 */
673	.globl	_cachectl
674_trap12:
675	movl	d1,sp@-			| push length
676	movl	a1,sp@-			| push addr
677	movl	d0,sp@-			| push command
678	jbsr	_cachectl		| do it
679	lea	sp@(12),sp		| pop args
680	jra	rei			| all done
681
682/*
683 * Trap 15 is used for:
684 *	- KGDB traps
685 *	- trace traps for SUN binaries (not fully supported yet)
686 * We just pass it on and let trap() sort it all out
687 */
688_trap15:
689	clrl	sp@-
690	moveml	#0xFFFF,sp@-
691#ifdef KGDB
692	moveq	#T_TRAP15,d0
693	movw	sp@(FR_HW),d1		| get PSW
694	andw	#PSL_S,d1		| from user mode?
695	jeq	fault			| yes, just a regular fault
696	movl	d0,sp@-
697	.globl	_kgdb_trap_glue
698	jbsr	_kgdb_trap_glue		| returns if no debugger
699	addl	#4,sp
700#endif
701	moveq	#T_TRAP15,d0
702	jra	fault
703
704/*
705 * Hit a breakpoint (trap 1 or 2) instruction.
706 * Push the code and treat as a normal fault.
707 */
708_trace:
709	clrl	sp@-
710	moveml	#0xFFFF,sp@-
711#ifdef KGDB
712	moveq	#T_TRACE,d0
713	movw	sp@(FR_HW),d1		| get SSW
714	andw	#PSL_S,d1		| from user mode?
715	jeq	fault			| no, regular fault
716	movl	d0,sp@-
717	jbsr	_kgdb_trap_glue		| returns if no debugger
718	addl	#4,sp
719#endif
720	moveq	#T_TRACE,d0
721	jra	fault
722
723/*
724 * The sigreturn() syscall comes here.  It requires special handling
725 * because we must open a hole in the stack to fill in the (possibly much
726 * larger) original stack frame.
727 */
728sigreturn:
729	lea	sp@(-84),sp		| leave enough space for largest frame
730	movl	sp@(84),sp@		| move up current 8 byte frame
731	movl	sp@(88),sp@(4)
732	movl	#84,sp@-		| default: adjust by 84 bytes
733	moveml	#0xFFFF,sp@-		| save user registers
734	movl	usp,a0			| save the user SP
735	movl	a0,sp@(FR_SP)		|   in the savearea
736	movl	#SYS_sigreturn,sp@-	| push syscall number
737	jbsr	_syscall		| handle it
738	addql	#4,sp			| pop syscall#
739	movl	sp@(FR_SP),a0		| grab and restore
740	movl	a0,usp			|   user SP
741	lea	sp@(FR_HW),a1		| pointer to HW frame
742	movw	sp@(FR_ADJ),d0		| do we need to adjust the stack?
743	jeq	Lsigr1			| no, just continue
744	moveq	#92,d1			| total size
745	subw	d0,d1			|  - hole size = frame size
746	lea	a1@(92),a0		| destination
747	addw	d1,a1			| source
748	lsrw	#1,d1			| convert to word count
749	subqw	#1,d1			| minus 1 for dbf
750Lsigrlp:
751	movw	a1@-,a0@-		| copy a word
752	dbf	d1,Lsigrlp		| continue
753	movl	a0,a1			| new HW frame base
754Lsigr1:
755	movl	a1,sp@(FR_SP)		| new SP value
756	moveml	sp@+,#0x7FFF		| restore user registers
757	movl	sp@,sp			| and our SP
758	jra	rei			| all done
759
760/*
761 * Interrupt handlers.
762 *
763 * For auto-vectored interrupts, the CPU provides the
764 * vector 0x18+level.  Note we count spurious interrupts,
765 * but don't do anything else with them.
766 *
767 * _intrhand_autovec is the entry point for auto-vectored
768 * interrupts.
769 *
770 * For vectored interrupts, we pull the pc, evec, and exception frame
771 * and pass them to the vectored interrupt dispatcher.  The vectored
772 * interrupt dispatcher will deal with strays.
773 *
774 * _intrhand_vectored is the entry point for vectored interrupts.
775 */
776
777#define INTERRUPT_SAVEREG	moveml  #0xC0C0,sp@-
778#define INTERRUPT_RESTOREREG	moveml  sp@+,#0x0303
779
780	.globl	_isrdispatch_autovec,_nmintr
781	.globl	_isrdispatch_vectored
782
783_spurintr:	/* Level 0 */
784	addql	#1,_intrcnt+0
785	addql	#1,_cnt+V_INTR
786	jra	rei
787
788_intrhand_autovec:	/* Levels 1 through 6 */
789	INTERRUPT_SAVEREG
790	movw	sp@(22),sp@-		| push exception vector
791	clrw	sp@-
792	jbsr	_isrdispatch_autovec	| call dispatcher
793	addql	#4,sp
794	INTERRUPT_RESTOREREG
795	jra	rei			| all done
796
797_lev7intr:	/* Level 7: NMI */
798	addql	#1,_intrcnt+32
799	clrl	sp@-
800	moveml	#0xFFFF,sp@-		| save registers
801	movl	usp,a0			| and save
802	movl	a0,sp@(FR_SP)		|   the user stack pointer
803	jbsr	_nmintr			| call handler: XXX wrapper
804	movl	sp@(FR_SP),a0		| restore
805	movl	a0,usp			|   user SP
806	moveml	sp@+,#0x7FFF		| and remaining registers
807	addql	#8,sp			| pop SP and stack adjust
808	jra	rei			| all done
809
810	.globl	_intrhand_vectored
811_intrhand_vectored:
812	INTERRUPT_SAVEREG
813	lea	sp@(16),a1		| get pointer to frame
814	movl	a1,sp@-
815	movw	sp@(26),d0
816	movl	d0,sp@-			| push exception vector info
817	movl	sp@(26),sp@-		| and PC
818	jbsr	_isrdispatch_vectored	| call dispatcher
819	lea	sp@(12),sp		| pop value args
820	INTERRUPT_RESTOREREG
821	jra	rei			| all done
822
823#undef INTERRUPT_SAVEREG
824#undef INTERRUPT_RESTOREREG
825
826/*
827 * Emulation of VAX REI instruction.
828 *
829 * This code deals with checking for and servicing ASTs
830 * (profiling, scheduling) and software interrupts (network, softclock).
831 * We check for ASTs first, just like the VAX.  To avoid excess overhead
832 * the T_ASTFLT handling code will also check for software interrupts so we
833 * do not have to do it here.  After identifing that we need an AST we
834 * drop the IPL to allow device interrupts.
835 *
836 * This code is complicated by the fact that sendsig may have been called
837 * necessitating a stack cleanup.
838 */
839	.comm	_ssir,1
840	.globl	_astpending
841	.globl	rei
842rei:
843	tstl	_astpending		| AST pending?
844	jeq	Lchksir			| no, go check for SIR
845Lrei1:
846	btst	#5,sp@			| yes, are we returning to user mode?
847	jne	Lchksir			| no, go check for SIR
848	movw	#PSL_LOWIPL,sr		| lower SPL
849	clrl	sp@-			| stack adjust
850	moveml	#0xFFFF,sp@-		| save all registers
851	movl	usp,a1			| including
852	movl	a1,sp@(FR_SP)		|    the users SP
853Lrei2:
854	clrl	sp@-			| VA == none
855	clrl	sp@-			| code == none
856	movl	#T_ASTFLT,sp@-		| type == async system trap
857	jbsr	_trap			| go handle it
858	lea	sp@(12),sp		| pop value args
859	movl	sp@(FR_SP),a0		| restore user SP
860	movl	a0,usp			|   from save area
861	movw	sp@(FR_ADJ),d0		| need to adjust stack?
862	jne	Laststkadj		| yes, go to it
863	moveml	sp@+,#0x7FFF		| no, restore most user regs
864	addql	#8,sp			| toss SP and stack adjust
865	rte				| and do real RTE
866Laststkadj:
867	lea	sp@(FR_HW),a1		| pointer to HW frame
868	addql	#8,a1			| source pointer
869	movl	a1,a0			| source
870	addw	d0,a0			|  + hole size = dest pointer
871	movl	a1@-,a0@-		| copy
872	movl	a1@-,a0@-		|  8 bytes
873	movl	a0,sp@(FR_SP)		| new SSP
874	moveml	sp@+,#0x7FFF		| restore user registers
875	movl	sp@,sp			| and our SP
876	rte				| and do real RTE
877Lchksir:
878	tstb	_ssir			| SIR pending?
879	jeq	Ldorte			| no, all done
880	movl	d0,sp@-			| need a scratch register
881	movw	sp@(4),d0		| get SR
882	andw	#PSL_IPL7,d0		| mask all but IPL
883	jne	Lnosir			| came from interrupt, no can do
884	movl	sp@+,d0			| restore scratch register
885Lgotsir:
886	movw	#SPL1,sr		| prevent others from servicing int
887	tstb	_ssir			| too late?
888	jeq	Ldorte			| yes, oh well...
889	clrl	sp@-			| stack adjust
890	moveml	#0xFFFF,sp@-		| save all registers
891	movl	usp,a1			| including
892	movl	a1,sp@(FR_SP)		|    the users SP
893Lsir1:
894	clrl	sp@-			| VA == none
895	clrl	sp@-			| code == none
896	movl	#T_SSIR,sp@-		| type == software interrupt
897	jbsr	_trap			| go handle it
898	lea	sp@(12),sp		| pop value args
899	movl	sp@(FR_SP),a0		| restore
900	movl	a0,usp			|   user SP
901	moveml	sp@+,#0x7FFF		| and all remaining registers
902	addql	#8,sp			| pop SP and stack adjust
903	rte
904Lnosir:
905	movl	sp@+,d0			| restore scratch register
906Ldorte:
907	rte				| real return
908
909/*
910 * Primitives
911 */
912
913/*
914 * Use common m68k support routines.
915 */
916#include <m68k/m68k/support.s>
917
918	.globl	_whichqs,_qs,_cnt,_panic
919	.globl	_curproc,_want_resched
920
921/*
922 * Use common m68k process manipulation routines.
923 */
924#include <m68k/m68k/proc_subr.s>
925
926Lsw0:
927	.asciz	"switch"
928	.even
929
930	.globl	_curpcb
931	.globl	_masterpaddr	| XXX compatibility (debuggers)
932	.data
933_masterpaddr:			| XXX compatibility (debuggers)
934_curpcb:
935	.long	0
936mdpflag:
937	.byte	0		| copy of proc md_flags low byte
938	.align	2
939	.comm	nullpcb,SIZEOF_PCB
940	.text
941
942/*
943 * At exit of a process, do a switch for the last time.
944 * Switch to a safe stack and PCB, and deallocate the process's resources.
945 */
946ENTRY(switch_exit)
947	movl    sp@(4),a0
948	movl    #nullpcb,_curpcb        | save state into garbage pcb
949	lea     tmpstk,sp               | goto a tmp stack
950
951	/* Free old process's resources. */
952	movl    #USPACE,sp@-            | size of u-area
953	movl    a0@(P_ADDR),sp@-        | address of process's u-area
954	movl    _kernel_map,sp@-        | map it was allocated in
955	jbsr    _kmem_free              | deallocate it
956	lea     sp@(12),sp              | pop args
957
958	jra	_cpu_switch
959
960/*
961 * When no processes are on the runq, Swtch branches to Idle
962 * to wait for something to come ready.
963 */
964	.globl	Idle
965Idle:
966	stop	#PSL_LOWIPL
967	movw	#PSL_HIGHIPL,sr
968	movl    _whichqs,d0
969	jeq     Idle
970	jra	Lsw1
971
972Lbadsw:
973	movl	#Lsw0,sp@-
974	jbsr	_panic
975	/*NOTREACHED*/
976
977/*
978 * cpu_switch()
979 *
980 * NOTE: On the mc68851 (318/319/330) we attempt to avoid flushing the
981 * entire ATC.  The effort involved in selective flushing may not be
982 * worth it, maybe we should just flush the whole thing?
983 *
984 * NOTE 2: With the new VM layout we now no longer know if an inactive
985 * user's PTEs have been changed (formerly denoted by the SPTECHG p_flag
986 * bit).  For now, we just always flush the full ATC.
987 */
988ENTRY(cpu_switch)
989	movl	_curpcb,a0		| current pcb
990	movw	sr,a0@(PCB_PS)		| save sr before changing ipl
991#ifdef notyet
992	movl	_curproc,sp@-		| remember last proc running
993#endif
994	clrl	_curproc
995
996	/*
997	 * Find the highest-priority queue that isn't empty,
998	 * then take the first proc from that queue.
999	 */
1000	movw    #PSL_HIGHIPL,sr         | lock out interrupts
1001	movl    _whichqs,d0
1002	jeq     Idle
1003Lsw1:
1004	movl    d0,d1
1005	negl    d0
1006	andl    d1,d0
1007	bfffo   d0{#0:#32},d1
1008	eorib   #31,d1
1009
1010	movl    d1,d0
1011	lslb    #3,d1                   | convert queue number to index
1012	addl    #_qs,d1                 | locate queue (q)
1013	movl    d1,a1
1014	movl    a1@(P_FORW),a0          | p = q->p_forw
1015	cmpal   d1,a0                   | anyone on queue?
1016	jeq     Lbadsw                  | no, panic
1017	movl    a0@(P_FORW),a1@(P_FORW) | q->p_forw = p->p_forw
1018	movl    a0@(P_FORW),a1          | n = p->p_forw
1019	movl    d1,a1@(P_BACK)          | n->p_back = q
1020	cmpal   d1,a1                   | anyone left on queue?
1021	jne     Lsw2                    | yes, skip
1022	movl    _whichqs,d1
1023	bclr    d0,d1                   | no, clear bit
1024	movl    d1,_whichqs
1025Lsw2:
1026	movl	a0,_curproc
1027	clrl	_want_resched
1028#ifdef notyet
1029	movl	sp@+,a1
1030	cmpl	a0,a1			| switching to same proc?
1031	jeq	Lswdone			| yes, skip save and restore
1032#endif
1033	/*
1034	 * Save state of previous process in its pcb.
1035	 */
1036	movl	_curpcb,a1
1037	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1038	movl	usp,a2			| grab USP (a2 has been saved)
1039	movl	a2,a1@(PCB_USP)		| and save it
1040#ifdef FPCOPROC
1041	lea	a1@(PCB_FPCTX),a2	| pointer to FP save area
1042	fsave	a2@			| save FP state
1043	tstb	a2@			| null state frame?
1044	jeq	Lswnofpsave		| yes, all done
1045	fmovem	fp0-fp7,a2@(216)	| save FP general registers
1046	fmovem	fpcr/fpsr/fpi,a2@(312)	| save FP control registers
1047Lswnofpsave:
1048#endif
1049
1050#ifdef DIAGNOSTIC
1051	tstl	a0@(P_WCHAN)
1052	jne	Lbadsw
1053	cmpb	#SRUN,a0@(P_STAT)
1054	jne	Lbadsw
1055#endif
1056	clrl	a0@(P_BACK)		| clear back link
1057	movb	a0@(P_MD_FLAGS+3),mdpflag | low byte of p_md.md_flags
1058	movl	a0@(P_ADDR),a1		| get p_addr
1059	movl	a1,_curpcb
1060
1061	/* see if pmap_activate needs to be called; should remove this */
1062	movl	a0@(P_VMSPACE),a0	| vmspace = p->p_vmspace
1063#ifdef DIAGNOSTIC
1064	tstl	a0			| map == VM_MAP_NULL?
1065	jeq	Lbadsw			| panic
1066#endif
1067	movl	a0@(VM_PMAP),a0		| pmap = vmspace->vm_map.pmap
1068	tstl	a0@(PM_STCHG)		| pmap->st_changed?
1069	jeq	Lswnochg		| no, skip
1070	pea	a1@			| push pcb (at p_addr)
1071	pea	a0@			| push pmap
1072	jbsr	_pmap_activate		| pmap_activate(pmap, pcb)
1073	addql	#8,sp
1074	movl	_curpcb,a1		| restore p_addr
1075Lswnochg:
1076
1077	lea     tmpstk,sp               | now goto a tmp stack for NMI
1078#if defined(M68040)
1079	cmpl	#MMU_68040,_mmutype	| 68040?
1080	jne	Lres1a			| no, skip
1081	.word	0xf518			| yes, pflusha
1082	movl	a1@(PCB_USTP),d0	| get USTP
1083	moveq	#PGSHIFT,d1
1084	lsll	d1,d0			| convert to addr
1085	.long	0x4e7b0806		| movc d0,urp
1086	jra	Lcxswdone
1087Lres1a:
1088#endif
1089	movl	#CACHE_CLR,d0
1090	movc	d0,cacr			| invalidate cache(s)
1091	pflusha				| flush entire TLB
1092	movl	a1@(PCB_USTP),d0	| get USTP
1093	moveq	#PGSHIFT,d1
1094	lsll	d1,d0			| convert to addr
1095	lea	_protorp,a0		| CRP prototype
1096	movl	d0,a0@(4)		| stash USTP
1097	pmove	a0@,crp			| load new user root pointer
1098Lcxswdone:
1099	moveml	a1@(PCB_REGS),#0xFCFC	| and registers
1100	movl	a1@(PCB_USP),a0
1101	movl	a0,usp			| and USP
1102#ifdef FPCOPROC
1103	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1104	tstb	a0@			| null state frame?
1105	jeq	Lresfprest		| yes, easy
1106#if defined(M68040)
1107	cmpl	#MMU_68040,_mmutype	| 68040?
1108	jne	Lresnot040		| no, skip
1109	clrl	sp@-			| yes...
1110	frestore sp@+			| ...magic!
1111Lresnot040:
1112#endif
1113	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
1114	fmovem	a0@(216),fp0-fp7	| restore FP general registers
1115Lresfprest:
1116	frestore a0@			| restore state
1117#endif
1118	movw	a1@(PCB_PS),sr		| no, restore PS
1119	moveq	#1,d0			| return 1 (for alternate returns)
1120	rts
1121
1122/*
1123 * savectx(pcb)
1124 * Update pcb, saving current processor state.
1125 */
1126ENTRY(savectx)
1127	movl	sp@(4),a1
1128	movw	sr,a1@(PCB_PS)
1129	movl	usp,a0			| grab USP
1130	movl	a0,a1@(PCB_USP)		| and save it
1131	moveml	#0xFCFC,a1@(PCB_REGS)	| save non-scratch registers
1132#ifdef FPCOPROC
1133	lea	a1@(PCB_FPCTX),a0	| pointer to FP save area
1134	fsave	a0@			| save FP state
1135	tstb	a0@			| null state frame?
1136	jeq	Lsvnofpsave		| yes, all done
1137	fmovem	fp0-fp7,a0@(216)	| save FP general registers
1138	fmovem	fpcr/fpsr/fpi,a0@(312)	| save FP control registers
1139Lsvnofpsave:
1140#endif
1141	moveq	#0,d0			| return 0
1142	rts
1143
1144#if defined(M68040)
1145ENTRY(suline)
1146	movl	sp@(4),a0		| address to write
1147	movl	_curpcb,a1		| current pcb
1148	movl	#Lslerr,a1@(PCB_ONFAULT) | where to return to on a fault
1149	movl	sp@(8),a1		| address of line
1150	movl	a1@+,d0			| get lword
1151	movsl	d0,a0@+			| put lword
1152	nop				| sync
1153	movl	a1@+,d0			| get lword
1154	movsl	d0,a0@+			| put lword
1155	nop				| sync
1156	movl	a1@+,d0			| get lword
1157	movsl	d0,a0@+			| put lword
1158	nop				| sync
1159	movl	a1@+,d0			| get lword
1160	movsl	d0,a0@+			| put lword
1161	nop				| sync
1162	moveq	#0,d0			| indicate no fault
1163	jra	Lsldone
1164Lslerr:
1165	moveq	#-1,d0
1166Lsldone:
1167	movl	_curpcb,a1		| current pcb
1168	clrl	a1@(PCB_ONFAULT)	| clear fault address
1169	rts
1170#endif
1171
1172/*
1173 * Invalidate entire TLB.
1174 */
1175ENTRY(TBIA)
1176__TBIA:
1177#if defined(M68040)
1178	cmpl	#MMU_68040,_mmutype	| 68040?
1179	jne	Lmotommu3		| no, skip
1180	.word	0xf518			| yes, pflusha
1181	rts
1182Lmotommu3:
1183#endif
1184	tstl	_mmutype		| what mmu?
1185	jpl	Lmc68851a		| 68851 implies no d-cache
1186	movl	#DC_CLEAR,d0
1187	movc	d0,cacr			| invalidate on-chip d-cache
1188Lmc68851a:
1189	rts
1190
1191/*
1192 * Invalidate any TLB entry for given VA (TB Invalidate Single)
1193 */
1194ENTRY(TBIS)
1195#ifdef DEBUG
1196	tstl	fulltflush		| being conservative?
1197	jne	__TBIA			| yes, flush entire TLB
1198#endif
1199#if defined(M68040)
1200	cmpl	#MMU_68040,_mmutype	| 68040?
1201	jne	Lmotommu4		| no, skip
1202	movl	sp@(4),a0
1203	movc	dfc,d1
1204	moveq	#1,d0			| user space
1205	movc	d0,dfc
1206	.word	0xf508			| pflush a0@
1207	moveq	#5,d0			| super space
1208	movc	d0,dfc
1209	.word	0xf508			| pflush a0@
1210	movc	d1,dfc
1211	rts
1212Lmotommu4:
1213#endif
1214	tstl	_mmutype		| is 68851?
1215	jpl	Lmc68851b		|
1216	movl	sp@(4),a0		| get addr to flush
1217	pflush	#0,#0,a0@		| flush address from both sides
1218	movl	#DC_CLEAR,d0
1219	movc	d0,cacr			| invalidate on-chip data cache
1220	rts
1221Lmc68851b:
1222	pflushs	#0,#0,a0@		| flush address from both sides
1223	rts
1224
1225/*
1226 * Invalidate supervisor side of TLB
1227 */
1228ENTRY(TBIAS)
1229#ifdef DEBUG
1230	tstl	fulltflush		| being conservative?
1231	jne	__TBIA			| yes, flush everything
1232#endif
1233#if defined(M68040)
1234	cmpl    #MMU_68040,_mmutype     | 68040?
1235	jne     Lmotommu5               | no, skip
1236	.word   0xf518                  | yes, pflusha (for now) XXX
1237	rts
1238Lmotommu5:
1239#endif
1240	pflush	#4,#4			| flush supervisor TLB entries
1241	movl	#DC_CLEAR,d0
1242	movc	d0,cacr			| invalidate on-chip d-cache
1243	rts
1244
1245/*
1246 * Invalidate user side of TLB
1247 */
1248ENTRY(TBIAU)
1249#ifdef DEBUG
1250	tstl	fulltflush		| being conservative?
1251	jne	__TBIA			| yes, flush everything
1252#endif
1253#if defined(M68040)
1254	cmpl    #MMU_68040,_mmutype     | 68040?
1255	jne     Lmotommu6               | no, skip
1256	.word   0xf518                  | yes, pflusha (for now) XXX
1257	rts
1258Lmotommu6:
1259#endif
1260	pflush	#0,#4			| flush user TLB entries
1261	movl	#DC_CLEAR,d0
1262	movc	d0,cacr			| invalidate on-chip d-cache
1263	rts
1264
1265/*
1266 * Invalidate instruction cache
1267 */
1268ENTRY(ICIA)
1269#if defined(M68040)
1270ENTRY(ICPA)
1271	cmpl    #MMU_68040,_mmutype     | 68040
1272	jne     Lmotommu7               | no, skip
1273	.word   0xf498                  | cinva ic
1274	rts
1275Lmotommu7:
1276#endif
1277	movl	#IC_CLEAR,d0
1278	movc	d0,cacr			| invalidate i-cache
1279	rts
1280
1281/*
1282 * Invalidate data cache.
1283 * NOTE: we do not flush 68030 on-chip cache as there are no aliasing
1284 * problems with DC_WA.  The only cases we have to worry about are context
1285 * switch and TLB changes, both of which are handled "in-line" in resume
1286 * and TBI*.
1287 */
1288ENTRY(DCIA)
1289__DCIA:
1290#if defined(M68040)
1291	cmpl    #MMU_68040,_mmutype     | 68040
1292	jne     Lmotommu8               | no, skip
1293	/* XXX implement */
1294	rts
1295Lmotommu8:
1296#endif
1297	rts
1298
1299ENTRY(DCIS)
1300__DCIS:
1301#if defined(M68040)
1302	cmpl    #MMU_68040,_mmutype     | 68040
1303	jne     Lmotommu9               | no, skip
1304	/* XXX implement */
1305	rts
1306Lmotommu9:
1307#endif
1308	rts
1309
1310ENTRY(DCIU)
1311__DCIU:
1312#if defined(M68040)
1313	cmpl    #MMU_68040,_mmutype     | 68040
1314	jne     LmotommuA               | no, skip
1315	/* XXX implement */
1316	rts
1317LmotommuA:
1318#endif
1319	rts
1320
1321#if defined(M68040)
1322ENTRY(ICPL)
1323	movl    sp@(4),a0               | address
1324	.word   0xf488                  | cinvl ic,a0@
1325	rts
1326ENTRY(ICPP)
1327	movl    sp@(4),a0               | address
1328	.word   0xf490                  | cinvp ic,a0@
1329	rts
1330ENTRY(DCPL)
1331	movl    sp@(4),a0               | address
1332	.word   0xf448                  | cinvl dc,a0@
1333	rts
1334ENTRY(DCPP)
1335	movl    sp@(4),a0               | address
1336	.word   0xf450                  | cinvp dc,a0@
1337	rts
1338ENTRY(DCPA)
1339	.word   0xf458                  | cinva dc
1340	rts
1341ENTRY(DCFL)
1342	movl    sp@(4),a0               | address
1343	.word   0xf468                  | cpushl dc,a0@
1344	rts
1345ENTRY(DCFP)
1346	movl    sp@(4),a0               | address
1347	.word   0xf470                  | cpushp dc,a0@
1348	rts
1349#endif
1350
1351ENTRY(PCIA)
1352#if defined(M68040)
1353ENTRY(DCFA)
1354	cmpl    #MMU_68040,_mmutype     | 68040
1355	jne     LmotommuB               | no, skip
1356	.word   0xf478                  | cpusha dc
1357	rts
1358LmotommuB:
1359#endif
1360	movl	#DC_CLEAR,d0
1361	movc	d0,cacr			| invalidate on-chip d-cache
1362	rts
1363
1364ENTRY(ecacheon)
1365	rts
1366
1367ENTRY(ecacheoff)
1368	rts
1369
1370/*
1371 * Get callers current SP value.
1372 * Note that simply taking the address of a local variable in a C function
1373 * doesn't work because callee saved registers may be outside the stack frame
1374 * defined by A6 (e.g. GCC generated code).
1375 */
1376	.globl	_getsp
1377_getsp:
1378	movl	sp,d0			| get current SP
1379	addql	#4,d0			| compensate for return address
1380	rts
1381
1382	.globl	_getsfc, _getdfc
1383_getsfc:
1384	movc	sfc,d0
1385	rts
1386_getdfc:
1387	movc	dfc,d0
1388	rts
1389
1390/*
1391 * Load a new user segment table pointer.
1392 */
1393ENTRY(loadustp)
1394	movl	sp@(4),d0		| new USTP
1395	moveq	#PGSHIFT, d1
1396	lsll	d1,d0			| convert to addr
1397#if defined(M68040)
1398	cmpl    #MMU_68040,_mmutype     | 68040?
1399	jne     LmotommuC               | no, skip
1400	.long   0x4e7b0806              | movc d0,urp
1401	rts
1402LmotommuC:
1403#endif
1404	lea	_protorp,a0		| CRP prototype
1405	movl	d0,a0@(4)		| stash USTP
1406	pmove	a0@,crp			| load root pointer
1407	movl	#DC_CLEAR,d0
1408	movc	d0,cacr			| invalidate on-chip d-cache
1409	rts				|   since pmove flushes TLB
1410
1411ENTRY(ploadw)
1412	movl	sp@(4),a0		| address to load
1413	ploadw	#1,a0@			| pre-load translation
1414	rts
1415
1416/*
1417 * Set processor priority level calls.  Most are implemented with
1418 * inline asm expansions.  However, spl0 requires special handling
1419 * as we need to check for our emulated software interrupts.
1420 */
1421
1422ENTRY(spl0)
1423	moveq	#0,d0
1424	movw	sr,d0			| get old SR for return
1425	movw	#PSL_LOWIPL,sr		| restore new SR
1426	tstb	_ssir			| software interrupt pending?
1427	jeq	Lspldone		| no, all done
1428	subql	#4,sp			| make room for RTE frame
1429	movl	sp@(4),sp@(2)		| position return address
1430	clrw	sp@(6)			| set frame type 0
1431	movw	#PSL_LOWIPL,sp@		| and new SR
1432	jra	Lgotsir			| go handle it
1433Lspldone:
1434	rts
1435
1436ENTRY(getsr)
1437	moveq	#0,d0
1438	movw	sr,d0
1439	rts
1440
1441/*
1442 * _delay(unsigned N)
1443 *
1444 * Delay for at least (N/256) microseconds.
1445 * This routine depends on the variable:  delay_divisor
1446 * which should be set based on the CPU clock rate.
1447 */
1448	.globl	__delay
1449__delay:
1450	| d0 = arg = (usecs << 8)
1451	movl	sp@(4),d0
1452	| d1 = delay_divisor
1453	movl	_delay_divisor,d1
1454L_delay:
1455	subl	d1,d0
1456	jgt	L_delay
1457	rts
1458
1459#ifdef FPCOPROC
1460/*
1461 * Save and restore 68881 state.
1462 */
1463ENTRY(m68881_save)
1464	movl	sp@(4),a0		| save area pointer
1465	fsave	a0@			| save state
1466	tstb	a0@			| null state frame?
1467	jeq	Lm68881sdone		| yes, all done
1468	fmovem fp0-fp7,a0@(216)		| save FP general registers
1469	fmovem fpcr/fpsr/fpi,a0@(312)	| save FP control registers
1470Lm68881sdone:
1471	rts
1472
1473ENTRY(m68881_restore)
1474	movl	sp@(4),a0		| save area pointer
1475	tstb	a0@			| null state frame?
1476	jeq	Lm68881rdone		| yes, easy
1477	fmovem	a0@(312),fpcr/fpsr/fpi	| restore FP control registers
1478	fmovem	a0@(216),fp0-fp7	| restore FP general registers
1479Lm68881rdone:
1480	frestore a0@			| restore state
1481	rts
1482#endif
1483
1484/*
1485 * Handle the nitty-gritty of rebooting the machine.
1486 * Basically we just turn off the MMU and jump to the appropriate ROM routine.
1487 */
1488	.globl	_doboot
1489_doboot:
1490#if defined(M68040)
1491	cmpl	#MMU_68040,_mmutype	| 68040?
1492	jeq	Lnocache5		| yes, skip
1493#endif
1494	movl	#CACHE_OFF,d0
1495	movc	d0,cacr			| disable on-chip cache(s)
1496Lnocache5:
1497	movl	_boothowto,d0		| load howto
1498					| (used to load bootdev in d1 here)
1499	movl	sp@(4),d2		| arg
1500	lea	tmpstk,sp		| physical SP in case of NMI
1501	movl	#0,a7@-			| value for pmove to TC (turn off MMU)
1502	pmove	a7@,tc			| disable MMU
1503	movl	#0, d3
1504	movc	d3,vbr			| ROM VBR
1505	andl	#RB_SBOOT, d0		| mask off
1506	tstl	d0			|
1507	bne	Lsboot			| sboot?
1508	/* NOT sboot */
1509	cmpl	#0, d2			| autoboot?
1510	beq	1f			| yes!
1511	trap	#15			| return to bug
1512	.short	MVMEPROM_EXIT		| exit
15131:	movl	#0xff800004,a0		| restart the BUG
1514	movl	a0@, a0			| get PC
1515	jmp	a0@			| go!
1516
1517Lsboot: /* sboot */
1518	cmpl	#0, d2			| autoboot?
1519	beq	1f			| yes!
1520	jmp 	0x4000			| back to sboot
15211:	jmp	0x400a			| tell sboot to reboot us
1522
1523	.data
1524	.globl	_machineid,_mmutype,_cputype,_ectype,_protorp,_prototc
1525_machineid:
1526	.long	MVME_147	| default to MVME_147
1527_mmutype:
1528	.long	MMU_68030	| default to MMU_68030
1529_cputype:
1530	.long	CPU_68030	| default to CPU_68030
1531_ectype:
1532	.long	EC_NONE		| external cache type, default to none
1533_protorp:
1534	.long	0,0		| prototype root pointer
1535_prototc:
1536	.long	0		| prototype translation control
1537	.globl	_bootpart,_bootdevlun,_bootctrllun,_bootaddr,_boothowto
1538_bootpart:
1539	.long	0
1540_bootdevlun:
1541	.long	0
1542_bootctrllun:
1543	.long	0
1544_bootaddr:
1545	.long	0
1546_boothowto:
1547	.long	0
1548	.globl	_cold
1549_cold:
1550	.long	1		| cold start flag
1551	.globl	_want_resched
1552_want_resched:
1553	.long	0
1554	.globl	_intiobase, _intiolimit
1555	.globl	_proc0paddr
1556_proc0paddr:
1557	.long	0		| KVA of proc0 u-area
1558_intiobase:
1559	.long	0		| KVA of base of internal IO space
1560_intiolimit:
1561	.long	0		| KVA of end of internal IO space
1562#ifdef DEBUG
1563	.globl	fulltflush, fullcflush
1564fulltflush:
1565	.long	0
1566fullcflush:
1567	.long	0
1568#endif
1569/* interrupt counters */
1570	.globl	_intrcnt,_eintrcnt,_intrnames,_eintrnames
1571_intrnames:
1572	.asciz	"spur"
1573	.asciz	"lev1"
1574	.asciz	"lev2"
1575	.asciz	"lev3"
1576	.asciz	"lev4"
1577	.asciz	"clock"
1578	.asciz	"lev6"
1579	.asciz	"nmi"
1580	.asciz	"statclock"
1581_eintrnames:
1582	.even
1583_intrcnt:
1584	.long	0,0,0,0,0,0,0,0,0,0
1585_eintrcnt:
1586
1587#include <mvme68k/mvme68k/vectors.s>
1588