1/* SPDX-License-Identifier: GPL-2.0-or-later */
2/*
3 *  PowerPC version
4 *    Copyright (C) 1995-1996 Gary Thomas (gdt@linuxppc.org)
5 *
6 *  Rewritten by Cort Dougan (cort@cs.nmt.edu) for PReP
7 *    Copyright (C) 1996 Cort Dougan <cort@cs.nmt.edu>
8 *  Adapted for Power Macintosh by Paul Mackerras.
9 *  Low-level exception handlers and MMU support
10 *  rewritten by Paul Mackerras.
11 *    Copyright (C) 1996 Paul Mackerras.
12 *  MPC8xx modifications Copyright (C) 1997 Dan Malek (dmalek@jlc.net).
13 *
14 *  This file contains the low-level support and setup for the
15 *  PowerPC platform, including trap and interrupt dispatch.
16 *  (The PPC 8xx embedded CPUs use head_8xx.S instead.)
17 */
18
19#include <linux/init.h>
20#include <linux/pgtable.h>
21#include <linux/linkage.h>
22
23#include <asm/reg.h>
24#include <asm/page.h>
25#include <asm/mmu.h>
26#include <asm/cputable.h>
27#include <asm/cache.h>
28#include <asm/thread_info.h>
29#include <asm/ppc_asm.h>
30#include <asm/asm-offsets.h>
31#include <asm/ptrace.h>
32#include <asm/bug.h>
33#include <asm/kvm_book3s_asm.h>
34#include <asm/export.h>
35#include <asm/feature-fixups.h>
36#include <asm/interrupt.h>
37
38#include "head_32.h"
39
40#define LOAD_BAT(n, reg, RA, RB)	\
41	/* see the comment for clear_bats() -- Cort */ \
42	li	RA,0;			\
43	mtspr	SPRN_IBAT##n##U,RA;	\
44	mtspr	SPRN_DBAT##n##U,RA;	\
45	lwz	RA,(n*16)+0(reg);	\
46	lwz	RB,(n*16)+4(reg);	\
47	mtspr	SPRN_IBAT##n##U,RA;	\
48	mtspr	SPRN_IBAT##n##L,RB;	\
49	lwz	RA,(n*16)+8(reg);	\
50	lwz	RB,(n*16)+12(reg);	\
51	mtspr	SPRN_DBAT##n##U,RA;	\
52	mtspr	SPRN_DBAT##n##L,RB
53
54	__HEAD
55_GLOBAL(_stext);
56
57/*
58 * _start is defined this way because the XCOFF loader in the OpenFirmware
59 * on the powermac expects the entry point to be a procedure descriptor.
60 */
61_GLOBAL(_start);
62	/*
63	 * These are here for legacy reasons, the kernel used to
64	 * need to look like a coff function entry for the pmac
65	 * but we're always started by some kind of bootloader now.
66	 *  -- Cort
67	 */
68	nop	/* used by __secondary_hold on prep (mtx) and chrp smp */
69	nop	/* used by __secondary_hold on prep (mtx) and chrp smp */
70	nop
71
72/* PMAC
73 * Enter here with the kernel text, data and bss loaded starting at
74 * 0, running with virtual == physical mapping.
75 * r5 points to the prom entry point (the client interface handler
76 * address).  Address translation is turned on, with the prom
77 * managing the hash table.  Interrupts are disabled.  The stack
78 * pointer (r1) points to just below the end of the half-meg region
79 * from 0x380000 - 0x400000, which is mapped in already.
80 *
81 * If we are booted from MacOS via BootX, we enter with the kernel
82 * image loaded somewhere, and the following values in registers:
83 *  r3: 'BooX' (0x426f6f58)
84 *  r4: virtual address of boot_infos_t
85 *  r5: 0
86 *
87 * PREP
88 * This is jumped to on prep systems right after the kernel is relocated
89 * to its proper place in memory by the boot loader.  The expected layout
90 * of the regs is:
91 *   r3: ptr to residual data
92 *   r4: initrd_start or if no initrd then 0
93 *   r5: initrd_end - unused if r4 is 0
94 *   r6: Start of command line string
95 *   r7: End of command line string
96 *
97 * This just gets a minimal mmu environment setup so we can call
98 * start_here() to do the real work.
99 * -- Cort
100 */
101
102	.globl	__start
103__start:
104/*
105 * We have to do any OF calls before we map ourselves to KERNELBASE,
106 * because OF may have I/O devices mapped into that area
107 * (particularly on CHRP).
108 */
109	cmpwi	0,r5,0
110	beq	1f
111
112#ifdef CONFIG_PPC_OF_BOOT_TRAMPOLINE
113	/* find out where we are now */
114	bcl	20,31,$+4
1150:	mflr	r8			/* r8 = runtime addr here */
116	addis	r8,r8,(_stext - 0b)@ha
117	addi	r8,r8,(_stext - 0b)@l	/* current runtime base addr */
118	bl	prom_init
119#endif /* CONFIG_PPC_OF_BOOT_TRAMPOLINE */
120
121	/* We never return. We also hit that trap if trying to boot
122	 * from OF while CONFIG_PPC_OF_BOOT_TRAMPOLINE isn't selected */
123	trap
124
125/*
126 * Check for BootX signature when supporting PowerMac and branch to
127 * appropriate trampoline if it's present
128 */
129#ifdef CONFIG_PPC_PMAC
1301:	lis	r31,0x426f
131	ori	r31,r31,0x6f58
132	cmpw	0,r3,r31
133	bne	1f
134	bl	bootx_init
135	trap
136#endif /* CONFIG_PPC_PMAC */
137
1381:	mr	r31,r3			/* save device tree ptr */
139	li	r24,0			/* cpu # */
140
141/*
142 * early_init() does the early machine identification and does
143 * the necessary low-level setup and clears the BSS
144 *  -- Cort <cort@fsmlabs.com>
145 */
146	bl	early_init
147
148/* Switch MMU off, clear BATs and flush TLB. At this point, r3 contains
149 * the physical address we are running at, returned by early_init()
150 */
151 	bl	mmu_off
152__after_mmu_off:
153	bl	clear_bats
154	bl	flush_tlbs
155
156	bl	initial_bats
157	bl	load_segment_registers
158	bl	reloc_offset
159	bl	early_hash_table
160#if defined(CONFIG_BOOTX_TEXT)
161	bl	setup_disp_bat
162#endif
163#ifdef CONFIG_PPC_EARLY_DEBUG_CPM
164	bl	setup_cpm_bat
165#endif
166#ifdef CONFIG_PPC_EARLY_DEBUG_USBGECKO
167	bl	setup_usbgecko_bat
168#endif
169
170/*
171 * Call setup_cpu for CPU 0 and initialize 6xx Idle
172 */
173	bl	reloc_offset
174	li	r24,0			/* cpu# */
175	bl	call_setup_cpu		/* Call setup_cpu for this CPU */
176	bl	reloc_offset
177	bl	init_idle_6xx
178
179
180/*
181 * We need to run with _start at physical address 0.
182 * On CHRP, we are loaded at 0x10000 since OF on CHRP uses
183 * the exception vectors at 0 (and therefore this copy
184 * overwrites OF's exception vectors with our own).
185 * The MMU is off at this point.
186 */
187	bl	reloc_offset
188	mr	r26,r3
189	addis	r4,r3,KERNELBASE@h	/* current address of _start */
190	lis	r5,PHYSICAL_START@h
191	cmplw	0,r4,r5			/* already running at PHYSICAL_START? */
192	bne	relocate_kernel
193/*
194 * we now have the 1st 16M of ram mapped with the bats.
195 * prep needs the mmu to be turned on here, but pmac already has it on.
196 * this shouldn't bother the pmac since it just gets turned on again
197 * as we jump to our code at KERNELBASE. -- Cort
198 * Actually no, pmac doesn't have it on any more. BootX enters with MMU
199 * off, and in other cases, we now turn it off before changing BATs above.
200 */
201turn_on_mmu:
202	mfmsr	r0
203	ori	r0,r0,MSR_DR|MSR_IR|MSR_RI
204	mtspr	SPRN_SRR1,r0
205	lis	r0,start_here@h
206	ori	r0,r0,start_here@l
207	mtspr	SPRN_SRR0,r0
208	rfi				/* enables MMU */
209
210/*
211 * We need __secondary_hold as a place to hold the other cpus on
212 * an SMP machine, even when we are running a UP kernel.
213 */
214	. = 0xc0			/* for prep bootloader */
215	li	r3,1			/* MTX only has 1 cpu */
216	.globl	__secondary_hold
217__secondary_hold:
218	/* tell the master we're here */
219	stw	r3,__secondary_hold_acknowledge@l(0)
220#ifdef CONFIG_SMP
221100:	lwz	r4,0(0)
222	/* wait until we're told to start */
223	cmpw	0,r4,r3
224	bne	100b
225	/* our cpu # was at addr 0 - go */
226	mr	r24,r3			/* cpu # */
227	b	__secondary_start
228#else
229	b	.
230#endif /* CONFIG_SMP */
231
232	.globl	__secondary_hold_spinloop
233__secondary_hold_spinloop:
234	.long	0
235	.globl	__secondary_hold_acknowledge
236__secondary_hold_acknowledge:
237	.long	-1
238
239/* System reset */
240/* core99 pmac starts the seconary here by changing the vector, and
241   putting it back to what it was (unknown_async_exception) when done.  */
242	EXCEPTION(INTERRUPT_SYSTEM_RESET, Reset, unknown_async_exception)
243
244/* Machine check */
245/*
246 * On CHRP, this is complicated by the fact that we could get a
247 * machine check inside RTAS, and we have no guarantee that certain
248 * critical registers will have the values we expect.  The set of
249 * registers that might have bad values includes all the GPRs
250 * and all the BATs.  We indicate that we are in RTAS by putting
251 * a non-zero value, the address of the exception frame to use,
252 * in thread.rtas_sp.  The machine check handler checks thread.rtas_sp
253 * and uses its value if it is non-zero.
254 * (Other exception handlers assume that r1 is a valid kernel stack
255 * pointer when we take an exception from supervisor mode.)
256 *	-- paulus.
257 */
258	START_EXCEPTION(INTERRUPT_MACHINE_CHECK, MachineCheck)
259	EXCEPTION_PROLOG_0
260#ifdef CONFIG_PPC_CHRP
261	mtspr	SPRN_SPRG_SCRATCH2,r1
262	mfspr	r1, SPRN_SPRG_THREAD
263	lwz	r1, RTAS_SP(r1)
264	cmpwi	cr1, r1, 0
265	bne	cr1, 7f
266	mfspr	r1, SPRN_SPRG_SCRATCH2
267#endif /* CONFIG_PPC_CHRP */
268	EXCEPTION_PROLOG_1
2697:	EXCEPTION_PROLOG_2 0x200 MachineCheck
270#ifdef CONFIG_PPC_CHRP
271	beq	cr1, 1f
272	twi	31, 0, 0
273#endif
2741:	prepare_transfer_to_handler
275	bl	machine_check_exception
276	b	interrupt_return
277
278/* Data access exception. */
279	START_EXCEPTION(INTERRUPT_DATA_STORAGE, DataAccess)
280#ifdef CONFIG_PPC_BOOK3S_604
281BEGIN_MMU_FTR_SECTION
282	mtspr	SPRN_SPRG_SCRATCH2,r10
283	mfspr	r10, SPRN_SPRG_THREAD
284	stw	r11, THR11(r10)
285	mfspr	r10, SPRN_DSISR
286	mfcr	r11
287	andis.	r10, r10, (DSISR_BAD_FAULT_32S | DSISR_DABRMATCH)@h
288	mfspr	r10, SPRN_SPRG_THREAD
289	beq	hash_page_dsi
290.Lhash_page_dsi_cont:
291	mtcr	r11
292	lwz	r11, THR11(r10)
293	mfspr	r10, SPRN_SPRG_SCRATCH2
294MMU_FTR_SECTION_ELSE
295	b	1f
296ALT_MMU_FTR_SECTION_END_IFSET(MMU_FTR_HPTE_TABLE)
297#endif
2981:	EXCEPTION_PROLOG_0 handle_dar_dsisr=1
299	EXCEPTION_PROLOG_1
300	EXCEPTION_PROLOG_2 INTERRUPT_DATA_STORAGE DataAccess handle_dar_dsisr=1
301	prepare_transfer_to_handler
302	lwz	r5, _DSISR(r1)
303	andis.	r0, r5, DSISR_DABRMATCH@h
304	bne-	1f
305	bl	do_page_fault
306	b	interrupt_return
3071:	bl	do_break
308	REST_NVGPRS(r1)
309	b	interrupt_return
310
311
312/* Instruction access exception. */
313	START_EXCEPTION(INTERRUPT_INST_STORAGE, InstructionAccess)
314	mtspr	SPRN_SPRG_SCRATCH0,r10
315	mtspr	SPRN_SPRG_SCRATCH1,r11
316	mfspr	r10, SPRN_SPRG_THREAD
317	mfspr	r11, SPRN_SRR0
318	stw	r11, SRR0(r10)
319	mfspr	r11, SPRN_SRR1		/* check whether user or kernel */
320	stw	r11, SRR1(r10)
321	mfcr	r10
322#ifdef CONFIG_PPC_BOOK3S_604
323BEGIN_MMU_FTR_SECTION
324	andis.	r11, r11, SRR1_ISI_NOPT@h	/* no pte found? */
325	bne	hash_page_isi
326.Lhash_page_isi_cont:
327	mfspr	r11, SPRN_SRR1		/* check whether user or kernel */
328END_MMU_FTR_SECTION_IFSET(MMU_FTR_HPTE_TABLE)
329#endif
330	andi.	r11, r11, MSR_PR
331
332	EXCEPTION_PROLOG_1
333	EXCEPTION_PROLOG_2 INTERRUPT_INST_STORAGE InstructionAccess
334	andis.	r5,r9,DSISR_SRR1_MATCH_32S@h /* Filter relevant SRR1 bits */
335	stw	r5, _DSISR(r11)
336	stw	r12, _DAR(r11)
337	prepare_transfer_to_handler
338	bl	do_page_fault
339	b	interrupt_return
340
341/* External interrupt */
342	EXCEPTION(INTERRUPT_EXTERNAL, HardwareInterrupt, do_IRQ)
343
344/* Alignment exception */
345	START_EXCEPTION(INTERRUPT_ALIGNMENT, Alignment)
346	EXCEPTION_PROLOG INTERRUPT_ALIGNMENT Alignment handle_dar_dsisr=1
347	prepare_transfer_to_handler
348	bl	alignment_exception
349	REST_NVGPRS(r1)
350	b	interrupt_return
351
352/* Program check exception */
353	START_EXCEPTION(INTERRUPT_PROGRAM, ProgramCheck)
354	EXCEPTION_PROLOG INTERRUPT_PROGRAM ProgramCheck
355	prepare_transfer_to_handler
356	bl	program_check_exception
357	REST_NVGPRS(r1)
358	b	interrupt_return
359
360/* Floating-point unavailable */
361	START_EXCEPTION(0x800, FPUnavailable)
362#ifdef CONFIG_PPC_FPU
363BEGIN_FTR_SECTION
364/*
365 * Certain Freescale cores don't have a FPU and treat fp instructions
366 * as a FP Unavailable exception.  Redirect to illegal/emulation handling.
367 */
368	b 	ProgramCheck
369END_FTR_SECTION_IFSET(CPU_FTR_FPU_UNAVAILABLE)
370	EXCEPTION_PROLOG INTERRUPT_FP_UNAVAIL FPUnavailable
371	beq	1f
372	bl	load_up_fpu		/* if from user, just load it up */
373	b	fast_exception_return
3741:	prepare_transfer_to_handler
375	bl	kernel_fp_unavailable_exception
376	b	interrupt_return
377#else
378	b 	ProgramCheck
379#endif
380
381/* Decrementer */
382	EXCEPTION(INTERRUPT_DECREMENTER, Decrementer, timer_interrupt)
383
384	EXCEPTION(0xa00, Trap_0a, unknown_exception)
385	EXCEPTION(0xb00, Trap_0b, unknown_exception)
386
387/* System call */
388	START_EXCEPTION(INTERRUPT_SYSCALL, SystemCall)
389	SYSCALL_ENTRY	INTERRUPT_SYSCALL
390
391	EXCEPTION(INTERRUPT_TRACE, SingleStep, single_step_exception)
392	EXCEPTION(0xe00, Trap_0e, unknown_exception)
393
394/*
395 * The Altivec unavailable trap is at 0x0f20.  Foo.
396 * We effectively remap it to 0x3000.
397 * We include an altivec unavailable exception vector even if
398 * not configured for Altivec, so that you can't panic a
399 * non-altivec kernel running on a machine with altivec just
400 * by executing an altivec instruction.
401 */
402	START_EXCEPTION(INTERRUPT_PERFMON, PerformanceMonitorTrap)
403	b	PerformanceMonitor
404
405	START_EXCEPTION(INTERRUPT_ALTIVEC_UNAVAIL, AltiVecUnavailableTrap)
406	b	AltiVecUnavailable
407
408	__HEAD
409/*
410 * Handle TLB miss for instruction on 603/603e.
411 * Note: we get an alternate set of r0 - r3 to use automatically.
412 */
413	. = INTERRUPT_INST_TLB_MISS_603
414InstructionTLBMiss:
415/*
416 * r0:	scratch
417 * r1:	linux style pte ( later becomes ppc hardware pte )
418 * r2:	ptr to linux-style pte
419 * r3:	scratch
420 */
421	/* Get PTE (linux-style) and check access */
422	mfspr	r3,SPRN_IMISS
423#ifdef CONFIG_MODULES
424	lis	r1, TASK_SIZE@h		/* check if kernel address */
425	cmplw	0,r1,r3
426#endif
427	mfspr	r2, SPRN_SDR1
428	li	r1,_PAGE_PRESENT | _PAGE_ACCESSED | _PAGE_EXEC | _PAGE_USER
429	rlwinm	r2, r2, 28, 0xfffff000
430#ifdef CONFIG_MODULES
431	bgt-	112f
432	lis	r2, (swapper_pg_dir - PAGE_OFFSET)@ha	/* if kernel address, use */
433	li	r1,_PAGE_PRESENT | _PAGE_ACCESSED | _PAGE_EXEC
434	addi	r2, r2, (swapper_pg_dir - PAGE_OFFSET)@l	/* kernel page table */
435#endif
436112:	rlwimi	r2,r3,12,20,29		/* insert top 10 bits of address */
437	lwz	r2,0(r2)		/* get pmd entry */
438	rlwinm.	r2,r2,0,0,19		/* extract address of pte page */
439	beq-	InstructionAddressInvalid	/* return if no mapping */
440	rlwimi	r2,r3,22,20,29		/* insert next 10 bits of address */
441	lwz	r0,0(r2)		/* get linux-style pte */
442	andc.	r1,r1,r0		/* check access & ~permission */
443	bne-	InstructionAddressInvalid /* return if access not permitted */
444	/* Convert linux-style PTE to low word of PPC-style PTE */
445	rlwimi	r0,r0,32-2,31,31	/* _PAGE_USER -> PP lsb */
446	ori	r1, r1, 0xe06		/* clear out reserved bits */
447	andc	r1, r0, r1		/* PP = user? 1 : 0 */
448BEGIN_FTR_SECTION
449	rlwinm	r1,r1,0,~_PAGE_COHERENT	/* clear M (coherence not required) */
450END_FTR_SECTION_IFCLR(CPU_FTR_NEED_COHERENT)
451	mtspr	SPRN_RPA,r1
452	tlbli	r3
453	mfspr	r3,SPRN_SRR1		/* Need to restore CR0 */
454	mtcrf	0x80,r3
455	rfi
456InstructionAddressInvalid:
457	mfspr	r3,SPRN_SRR1
458	rlwinm	r1,r3,9,6,6	/* Get load/store bit */
459
460	addis	r1,r1,0x2000
461	mtspr	SPRN_DSISR,r1	/* (shouldn't be needed) */
462	andi.	r2,r3,0xFFFF	/* Clear upper bits of SRR1 */
463	or	r2,r2,r1
464	mtspr	SPRN_SRR1,r2
465	mfspr	r1,SPRN_IMISS	/* Get failing address */
466	rlwinm.	r2,r2,0,31,31	/* Check for little endian access */
467	rlwimi	r2,r2,1,30,30	/* change 1 -> 3 */
468	xor	r1,r1,r2
469	mtspr	SPRN_DAR,r1	/* Set fault address */
470	mfmsr	r0		/* Restore "normal" registers */
471	xoris	r0,r0,MSR_TGPR>>16
472	mtcrf	0x80,r3		/* Restore CR0 */
473	mtmsr	r0
474	b	InstructionAccess
475
476/*
477 * Handle TLB miss for DATA Load operation on 603/603e
478 */
479	. = INTERRUPT_DATA_LOAD_TLB_MISS_603
480DataLoadTLBMiss:
481/*
482 * r0:	scratch
483 * r1:	linux style pte ( later becomes ppc hardware pte )
484 * r2:	ptr to linux-style pte
485 * r3:	scratch
486 */
487	/* Get PTE (linux-style) and check access */
488	mfspr	r3,SPRN_DMISS
489	lis	r1, TASK_SIZE@h		/* check if kernel address */
490	cmplw	0,r1,r3
491	mfspr	r2, SPRN_SDR1
492	li	r1, _PAGE_PRESENT | _PAGE_ACCESSED | _PAGE_USER
493	rlwinm	r2, r2, 28, 0xfffff000
494	bgt-	112f
495	lis	r2, (swapper_pg_dir - PAGE_OFFSET)@ha	/* if kernel address, use */
496	li	r1, _PAGE_PRESENT | _PAGE_ACCESSED
497	addi	r2, r2, (swapper_pg_dir - PAGE_OFFSET)@l	/* kernel page table */
498112:	rlwimi	r2,r3,12,20,29		/* insert top 10 bits of address */
499	lwz	r2,0(r2)		/* get pmd entry */
500	rlwinm.	r2,r2,0,0,19		/* extract address of pte page */
501	beq-	DataAddressInvalid	/* return if no mapping */
502	rlwimi	r2,r3,22,20,29		/* insert next 10 bits of address */
503	lwz	r0,0(r2)		/* get linux-style pte */
504	andc.	r1,r1,r0		/* check access & ~permission */
505	bne-	DataAddressInvalid	/* return if access not permitted */
506	/* Convert linux-style PTE to low word of PPC-style PTE */
507	rlwinm	r1,r0,32-9,30,30	/* _PAGE_RW -> PP msb */
508	rlwimi	r0,r0,32-1,30,30	/* _PAGE_USER -> PP msb */
509	rlwimi	r1,r0,32-3,24,24	/* _PAGE_RW -> _PAGE_DIRTY */
510	rlwimi	r0,r0,32-1,31,31	/* _PAGE_USER -> PP lsb */
511	xori	r1,r1,_PAGE_DIRTY	/* clear dirty when not rw */
512	ori	r1,r1,0xe04		/* clear out reserved bits */
513	andc	r1,r0,r1		/* PP = user? rw? 1: 3: 0 */
514BEGIN_FTR_SECTION
515	rlwinm	r1,r1,0,~_PAGE_COHERENT	/* clear M (coherence not required) */
516END_FTR_SECTION_IFCLR(CPU_FTR_NEED_COHERENT)
517	mtspr	SPRN_RPA,r1
518BEGIN_MMU_FTR_SECTION
519	li	r0,1
520	mfspr	r1,SPRN_SPRG_603_LRU
521	rlwinm	r2,r3,20,27,31		/* Get Address bits 15:19 */
522	slw	r0,r0,r2
523	xor	r1,r0,r1
524	srw	r0,r1,r2
525	mtspr   SPRN_SPRG_603_LRU,r1
526	mfspr	r2,SPRN_SRR1
527	rlwimi	r2,r0,31-14,14,14
528	mtspr   SPRN_SRR1,r2
529	mtcrf	0x80,r2
530	tlbld	r3
531	rfi
532MMU_FTR_SECTION_ELSE
533	mfspr	r2,SPRN_SRR1		/* Need to restore CR0 */
534	mtcrf	0x80,r2
535	tlbld	r3
536	rfi
537ALT_MMU_FTR_SECTION_END_IFSET(MMU_FTR_NEED_DTLB_SW_LRU)
538DataAddressInvalid:
539	mfspr	r3,SPRN_SRR1
540	rlwinm	r1,r3,9,6,6	/* Get load/store bit */
541	addis	r1,r1,0x2000
542	mtspr	SPRN_DSISR,r1
543	andi.	r2,r3,0xFFFF	/* Clear upper bits of SRR1 */
544	mtspr	SPRN_SRR1,r2
545	mfspr	r1,SPRN_DMISS	/* Get failing address */
546	rlwinm.	r2,r2,0,31,31	/* Check for little endian access */
547	beq	20f		/* Jump if big endian */
548	xori	r1,r1,3
54920:	mtspr	SPRN_DAR,r1	/* Set fault address */
550	mfmsr	r0		/* Restore "normal" registers */
551	xoris	r0,r0,MSR_TGPR>>16
552	mtcrf	0x80,r3		/* Restore CR0 */
553	mtmsr	r0
554	b	DataAccess
555
556/*
557 * Handle TLB miss for DATA Store on 603/603e
558 */
559	. = INTERRUPT_DATA_STORE_TLB_MISS_603
560DataStoreTLBMiss:
561/*
562 * r0:	scratch
563 * r1:	linux style pte ( later becomes ppc hardware pte )
564 * r2:	ptr to linux-style pte
565 * r3:	scratch
566 */
567	/* Get PTE (linux-style) and check access */
568	mfspr	r3,SPRN_DMISS
569	lis	r1, TASK_SIZE@h		/* check if kernel address */
570	cmplw	0,r1,r3
571	mfspr	r2, SPRN_SDR1
572	li	r1, _PAGE_RW | _PAGE_DIRTY | _PAGE_PRESENT | _PAGE_ACCESSED | _PAGE_USER
573	rlwinm	r2, r2, 28, 0xfffff000
574	bgt-	112f
575	lis	r2, (swapper_pg_dir - PAGE_OFFSET)@ha	/* if kernel address, use */
576	li	r1, _PAGE_RW | _PAGE_DIRTY | _PAGE_PRESENT | _PAGE_ACCESSED
577	addi	r2, r2, (swapper_pg_dir - PAGE_OFFSET)@l	/* kernel page table */
578112:	rlwimi	r2,r3,12,20,29		/* insert top 10 bits of address */
579	lwz	r2,0(r2)		/* get pmd entry */
580	rlwinm.	r2,r2,0,0,19		/* extract address of pte page */
581	beq-	DataAddressInvalid	/* return if no mapping */
582	rlwimi	r2,r3,22,20,29		/* insert next 10 bits of address */
583	lwz	r0,0(r2)		/* get linux-style pte */
584	andc.	r1,r1,r0		/* check access & ~permission */
585	bne-	DataAddressInvalid	/* return if access not permitted */
586	/* Convert linux-style PTE to low word of PPC-style PTE */
587	rlwimi	r0,r0,32-2,31,31	/* _PAGE_USER -> PP lsb */
588	li	r1,0xe06		/* clear out reserved bits & PP msb */
589	andc	r1,r0,r1		/* PP = user? 1: 0 */
590BEGIN_FTR_SECTION
591	rlwinm	r1,r1,0,~_PAGE_COHERENT	/* clear M (coherence not required) */
592END_FTR_SECTION_IFCLR(CPU_FTR_NEED_COHERENT)
593	mtspr	SPRN_RPA,r1
594	mfspr	r2,SPRN_SRR1		/* Need to restore CR0 */
595	mtcrf	0x80,r2
596BEGIN_MMU_FTR_SECTION
597	li	r0,1
598	mfspr	r1,SPRN_SPRG_603_LRU
599	rlwinm	r2,r3,20,27,31		/* Get Address bits 15:19 */
600	slw	r0,r0,r2
601	xor	r1,r0,r1
602	srw	r0,r1,r2
603	mtspr   SPRN_SPRG_603_LRU,r1
604	mfspr	r2,SPRN_SRR1
605	rlwimi	r2,r0,31-14,14,14
606	mtspr   SPRN_SRR1,r2
607	mtcrf	0x80,r2
608	tlbld	r3
609	rfi
610MMU_FTR_SECTION_ELSE
611	mfspr	r2,SPRN_SRR1		/* Need to restore CR0 */
612	mtcrf	0x80,r2
613	tlbld	r3
614	rfi
615ALT_MMU_FTR_SECTION_END_IFSET(MMU_FTR_NEED_DTLB_SW_LRU)
616
617#ifndef CONFIG_ALTIVEC
618#define altivec_assist_exception	unknown_exception
619#endif
620
621#ifndef CONFIG_TAU_INT
622#define TAUException	unknown_async_exception
623#endif
624
625	EXCEPTION(0x1300, Trap_13, instruction_breakpoint_exception)
626	EXCEPTION(0x1400, SMI, SMIException)
627	EXCEPTION(0x1500, Trap_15, unknown_exception)
628	EXCEPTION(0x1600, Trap_16, altivec_assist_exception)
629	EXCEPTION(0x1700, Trap_17, TAUException)
630	EXCEPTION(0x1800, Trap_18, unknown_exception)
631	EXCEPTION(0x1900, Trap_19, unknown_exception)
632	EXCEPTION(0x1a00, Trap_1a, unknown_exception)
633	EXCEPTION(0x1b00, Trap_1b, unknown_exception)
634	EXCEPTION(0x1c00, Trap_1c, unknown_exception)
635	EXCEPTION(0x1d00, Trap_1d, unknown_exception)
636	EXCEPTION(0x1e00, Trap_1e, unknown_exception)
637	EXCEPTION(0x1f00, Trap_1f, unknown_exception)
638	EXCEPTION(0x2000, RunMode, RunModeException)
639	EXCEPTION(0x2100, Trap_21, unknown_exception)
640	EXCEPTION(0x2200, Trap_22, unknown_exception)
641	EXCEPTION(0x2300, Trap_23, unknown_exception)
642	EXCEPTION(0x2400, Trap_24, unknown_exception)
643	EXCEPTION(0x2500, Trap_25, unknown_exception)
644	EXCEPTION(0x2600, Trap_26, unknown_exception)
645	EXCEPTION(0x2700, Trap_27, unknown_exception)
646	EXCEPTION(0x2800, Trap_28, unknown_exception)
647	EXCEPTION(0x2900, Trap_29, unknown_exception)
648	EXCEPTION(0x2a00, Trap_2a, unknown_exception)
649	EXCEPTION(0x2b00, Trap_2b, unknown_exception)
650	EXCEPTION(0x2c00, Trap_2c, unknown_exception)
651	EXCEPTION(0x2d00, Trap_2d, unknown_exception)
652	EXCEPTION(0x2e00, Trap_2e, unknown_exception)
653	EXCEPTION(0x2f00, Trap_2f, unknown_exception)
654
655	__HEAD
656	. = 0x3000
657
658#ifdef CONFIG_PPC_BOOK3S_604
659.macro save_regs_thread		thread
660	stw	r0, THR0(\thread)
661	stw	r3, THR3(\thread)
662	stw	r4, THR4(\thread)
663	stw	r5, THR5(\thread)
664	stw	r6, THR6(\thread)
665	stw	r8, THR8(\thread)
666	stw	r9, THR9(\thread)
667	mflr	r0
668	stw	r0, THLR(\thread)
669	mfctr	r0
670	stw	r0, THCTR(\thread)
671.endm
672
673.macro restore_regs_thread	thread
674	lwz	r0, THLR(\thread)
675	mtlr	r0
676	lwz	r0, THCTR(\thread)
677	mtctr	r0
678	lwz	r0, THR0(\thread)
679	lwz	r3, THR3(\thread)
680	lwz	r4, THR4(\thread)
681	lwz	r5, THR5(\thread)
682	lwz	r6, THR6(\thread)
683	lwz	r8, THR8(\thread)
684	lwz	r9, THR9(\thread)
685.endm
686
687hash_page_dsi:
688	save_regs_thread	r10
689	mfdsisr	r3
690	mfdar	r4
691	mfsrr0	r5
692	mfsrr1	r9
693	rlwinm	r3, r3, 32 - 15, _PAGE_RW	/* DSISR_STORE -> _PAGE_RW */
694	bl	hash_page
695	mfspr	r10, SPRN_SPRG_THREAD
696	restore_regs_thread r10
697	b	.Lhash_page_dsi_cont
698
699hash_page_isi:
700	mr	r11, r10
701	mfspr	r10, SPRN_SPRG_THREAD
702	save_regs_thread	r10
703	li	r3, 0
704	lwz	r4, SRR0(r10)
705	lwz	r9, SRR1(r10)
706	bl	hash_page
707	mfspr	r10, SPRN_SPRG_THREAD
708	restore_regs_thread r10
709	mr	r10, r11
710	b	.Lhash_page_isi_cont
711
712	.globl fast_hash_page_return
713fast_hash_page_return:
714	andis.	r10, r9, SRR1_ISI_NOPT@h	/* Set on ISI, cleared on DSI */
715	mfspr	r10, SPRN_SPRG_THREAD
716	restore_regs_thread r10
717	bne	1f
718
719	/* DSI */
720	mtcr	r11
721	lwz	r11, THR11(r10)
722	mfspr	r10, SPRN_SPRG_SCRATCH2
723	rfi
724
7251:	/* ISI */
726	mtcr	r11
727	mfspr	r11, SPRN_SPRG_SCRATCH1
728	mfspr	r10, SPRN_SPRG_SCRATCH0
729	rfi
730#endif /* CONFIG_PPC_BOOK3S_604 */
731
732#ifdef CONFIG_VMAP_STACK
733	vmap_stack_overflow_exception
734#endif
735
736	__HEAD
737AltiVecUnavailable:
738	EXCEPTION_PROLOG 0xf20 AltiVecUnavailable
739#ifdef CONFIG_ALTIVEC
740	beq	1f
741	bl	load_up_altivec		/* if from user, just load it up */
742	b	fast_exception_return
743#endif /* CONFIG_ALTIVEC */
7441:	prepare_transfer_to_handler
745	bl	altivec_unavailable_exception
746	b	interrupt_return
747
748	__HEAD
749PerformanceMonitor:
750	EXCEPTION_PROLOG 0xf00 PerformanceMonitor
751	prepare_transfer_to_handler
752	bl	performance_monitor_exception
753	b	interrupt_return
754
755
756	__HEAD
757/*
758 * This code is jumped to from the startup code to copy
759 * the kernel image to physical address PHYSICAL_START.
760 */
761relocate_kernel:
762	lis	r3,PHYSICAL_START@h	/* Destination base address */
763	li	r6,0			/* Destination offset */
764	li	r5,0x4000		/* # bytes of memory to copy */
765	bl	copy_and_flush		/* copy the first 0x4000 bytes */
766	addi	r0,r3,4f@l		/* jump to the address of 4f */
767	mtctr	r0			/* in copy and do the rest. */
768	bctr				/* jump to the copy */
7694:	lis	r5,_end-KERNELBASE@h
770	ori	r5,r5,_end-KERNELBASE@l
771	bl	copy_and_flush		/* copy the rest */
772	b	turn_on_mmu
773
774/*
775 * Copy routine used to copy the kernel to start at physical address 0
776 * and flush and invalidate the caches as needed.
777 * r3 = dest addr, r4 = source addr, r5 = copy limit, r6 = start offset
778 * on exit, r3, r4, r5 are unchanged, r6 is updated to be >= r5.
779 */
780_GLOBAL(copy_and_flush)
781	addi	r5,r5,-4
782	addi	r6,r6,-4
7834:	li	r0,L1_CACHE_BYTES/4
784	mtctr	r0
7853:	addi	r6,r6,4			/* copy a cache line */
786	lwzx	r0,r6,r4
787	stwx	r0,r6,r3
788	bdnz	3b
789	dcbst	r6,r3			/* write it to memory */
790	sync
791	icbi	r6,r3			/* flush the icache line */
792	cmplw	0,r6,r5
793	blt	4b
794	sync				/* additional sync needed on g4 */
795	isync
796	addi	r5,r5,4
797	addi	r6,r6,4
798	blr
799
800#ifdef CONFIG_SMP
801	.globl __secondary_start_mpc86xx
802__secondary_start_mpc86xx:
803	mfspr	r3, SPRN_PIR
804	stw	r3, __secondary_hold_acknowledge@l(0)
805	mr	r24, r3			/* cpu # */
806	b	__secondary_start
807
808	.globl	__secondary_start_pmac_0
809__secondary_start_pmac_0:
810	/* NB the entries for cpus 0, 1, 2 must each occupy 8 bytes. */
811	li	r24,0
812	b	1f
813	li	r24,1
814	b	1f
815	li	r24,2
816	b	1f
817	li	r24,3
8181:
819	/* on powersurge, we come in here with IR=0 and DR=1, and DBAT 0
820	   set to map the 0xf0000000 - 0xffffffff region */
821	mfmsr	r0
822	rlwinm	r0,r0,0,28,26		/* clear DR (0x10) */
823	mtmsr	r0
824	isync
825
826	.globl	__secondary_start
827__secondary_start:
828	/* Copy some CPU settings from CPU 0 */
829	bl	__restore_cpu_setup
830
831	lis	r3,-KERNELBASE@h
832	mr	r4,r24
833	bl	call_setup_cpu		/* Call setup_cpu for this CPU */
834	lis	r3,-KERNELBASE@h
835	bl	init_idle_6xx
836
837	/* get current's stack and current */
838	lis	r2,secondary_current@ha
839	tophys(r2,r2)
840	lwz	r2,secondary_current@l(r2)
841	tophys(r1,r2)
842	lwz	r1,TASK_STACK(r1)
843
844	/* stack */
845	addi	r1,r1,THREAD_SIZE-STACK_FRAME_MIN_SIZE
846	li	r0,0
847	tophys(r3,r1)
848	stw	r0,0(r3)
849
850	/* load up the MMU */
851	bl	load_segment_registers
852	bl	load_up_mmu
853
854	/* ptr to phys current thread */
855	tophys(r4,r2)
856	addi	r4,r4,THREAD	/* phys address of our thread_struct */
857	mtspr	SPRN_SPRG_THREAD,r4
858BEGIN_MMU_FTR_SECTION
859	lis	r4, (swapper_pg_dir - PAGE_OFFSET)@h
860	ori	r4, r4, (swapper_pg_dir - PAGE_OFFSET)@l
861	rlwinm	r4, r4, 4, 0xffff01ff
862	mtspr	SPRN_SDR1, r4
863END_MMU_FTR_SECTION_IFCLR(MMU_FTR_HPTE_TABLE)
864
865	/* enable MMU and jump to start_secondary */
866	li	r4,MSR_KERNEL
867	lis	r3,start_secondary@h
868	ori	r3,r3,start_secondary@l
869	mtspr	SPRN_SRR0,r3
870	mtspr	SPRN_SRR1,r4
871	rfi
872#endif /* CONFIG_SMP */
873
874#ifdef CONFIG_KVM_BOOK3S_HANDLER
875#include "../kvm/book3s_rmhandlers.S"
876#endif
877
878/*
879 * Load stuff into the MMU.  Intended to be called with
880 * IR=0 and DR=0.
881 */
882SYM_FUNC_START_LOCAL(early_hash_table)
883	sync			/* Force all PTE updates to finish */
884	isync
885	tlbia			/* Clear all TLB entries */
886	sync			/* wait for tlbia/tlbie to finish */
887	TLBSYNC			/* ... on all CPUs */
888	/* Load the SDR1 register (hash table base & size) */
889	lis	r6, early_hash - PAGE_OFFSET@h
890	ori	r6, r6, 3	/* 256kB table */
891	mtspr	SPRN_SDR1, r6
892	blr
893SYM_FUNC_END(early_hash_table)
894
895SYM_FUNC_START_LOCAL(load_up_mmu)
896	sync			/* Force all PTE updates to finish */
897	isync
898	tlbia			/* Clear all TLB entries */
899	sync			/* wait for tlbia/tlbie to finish */
900	TLBSYNC			/* ... on all CPUs */
901BEGIN_MMU_FTR_SECTION
902	/* Load the SDR1 register (hash table base & size) */
903	lis	r6,_SDR1@ha
904	tophys(r6,r6)
905	lwz	r6,_SDR1@l(r6)
906	mtspr	SPRN_SDR1,r6
907END_MMU_FTR_SECTION_IFSET(MMU_FTR_HPTE_TABLE)
908
909/* Load the BAT registers with the values set up by MMU_init. */
910	lis	r3,BATS@ha
911	addi	r3,r3,BATS@l
912	tophys(r3,r3)
913	LOAD_BAT(0,r3,r4,r5)
914	LOAD_BAT(1,r3,r4,r5)
915	LOAD_BAT(2,r3,r4,r5)
916	LOAD_BAT(3,r3,r4,r5)
917BEGIN_MMU_FTR_SECTION
918	LOAD_BAT(4,r3,r4,r5)
919	LOAD_BAT(5,r3,r4,r5)
920	LOAD_BAT(6,r3,r4,r5)
921	LOAD_BAT(7,r3,r4,r5)
922END_MMU_FTR_SECTION_IFSET(MMU_FTR_USE_HIGH_BATS)
923	blr
924SYM_FUNC_END(load_up_mmu)
925
926_GLOBAL(load_segment_registers)
927	li	r0, NUM_USER_SEGMENTS /* load up user segment register values */
928	mtctr	r0		/* for context 0 */
929#ifdef CONFIG_PPC_KUEP
930	lis	r3, SR_NX@h	/* Kp = 0, Ks = 0, VSID = 0 */
931#else
932	li	r3, 0		/* Kp = 0, Ks = 0, VSID = 0 */
933#endif
934	li	r4, 0
9353:	mtsrin	r3, r4
936	addi	r3, r3, 0x111	/* increment VSID */
937	addis	r4, r4, 0x1000	/* address of next segment */
938	bdnz	3b
939	li	r0, 16 - NUM_USER_SEGMENTS /* load up kernel segment registers */
940	mtctr	r0			/* for context 0 */
941	rlwinm	r3, r3, 0, ~SR_NX	/* Nx = 0 */
942	rlwinm	r3, r3, 0, ~SR_KS	/* Ks = 0 */
943	oris	r3, r3, SR_KP@h		/* Kp = 1 */
9443:	mtsrin	r3, r4
945	addi	r3, r3, 0x111	/* increment VSID */
946	addis	r4, r4, 0x1000	/* address of next segment */
947	bdnz	3b
948	blr
949
950/*
951 * This is where the main kernel code starts.
952 */
953start_here:
954	/* ptr to current */
955	lis	r2,init_task@h
956	ori	r2,r2,init_task@l
957	/* Set up for using our exception vectors */
958	/* ptr to phys current thread */
959	tophys(r4,r2)
960	addi	r4,r4,THREAD	/* init task's THREAD */
961	mtspr	SPRN_SPRG_THREAD,r4
962BEGIN_MMU_FTR_SECTION
963	lis	r4, (swapper_pg_dir - PAGE_OFFSET)@h
964	ori	r4, r4, (swapper_pg_dir - PAGE_OFFSET)@l
965	rlwinm	r4, r4, 4, 0xffff01ff
966	mtspr	SPRN_SDR1, r4
967END_MMU_FTR_SECTION_IFCLR(MMU_FTR_HPTE_TABLE)
968
969	/* stack */
970	lis	r1,init_thread_union@ha
971	addi	r1,r1,init_thread_union@l
972	li	r0,0
973	stwu	r0,THREAD_SIZE-STACK_FRAME_MIN_SIZE(r1)
974/*
975 * Do early platform-specific initialization,
976 * and set up the MMU.
977 */
978#ifdef CONFIG_KASAN
979	bl	kasan_early_init
980#endif
981	li	r3,0
982	mr	r4,r31
983	bl	machine_init
984	bl	__save_cpu_setup
985	bl	MMU_init
986	bl	MMU_init_hw_patch
987
988/*
989 * Go back to running unmapped so we can load up new values
990 * for SDR1 (hash table pointer) and the segment registers
991 * and change to using our exception vectors.
992 */
993	lis	r4,2f@h
994	ori	r4,r4,2f@l
995	tophys(r4,r4)
996	li	r3,MSR_KERNEL & ~(MSR_IR|MSR_DR)
997
998	.align	4
999	mtspr	SPRN_SRR0,r4
1000	mtspr	SPRN_SRR1,r3
1001	rfi
1002/* Load up the kernel context */
10032:	bl	load_up_mmu
1004
1005#ifdef CONFIG_BDI_SWITCH
1006	/* Add helper information for the Abatron bdiGDB debugger.
1007	 * We do this here because we know the mmu is disabled, and
1008	 * will be enabled for real in just a few instructions.
1009	 */
1010	lis	r5, abatron_pteptrs@h
1011	ori	r5, r5, abatron_pteptrs@l
1012	stw	r5, 0xf0(0)	/* This much match your Abatron config */
1013	lis	r6, swapper_pg_dir@h
1014	ori	r6, r6, swapper_pg_dir@l
1015	tophys(r5, r5)
1016	stw	r6, 0(r5)
1017#endif /* CONFIG_BDI_SWITCH */
1018
1019/* Now turn on the MMU for real! */
1020	li	r4,MSR_KERNEL
1021	lis	r3,start_kernel@h
1022	ori	r3,r3,start_kernel@l
1023	mtspr	SPRN_SRR0,r3
1024	mtspr	SPRN_SRR1,r4
1025	rfi
1026
1027/*
1028 * An undocumented "feature" of 604e requires that the v bit
1029 * be cleared before changing BAT values.
1030 *
1031 * Also, newer IBM firmware does not clear bat3 and 4 so
1032 * this makes sure it's done.
1033 *  -- Cort
1034 */
1035SYM_FUNC_START_LOCAL(clear_bats)
1036	li	r10,0
1037
1038	mtspr	SPRN_DBAT0U,r10
1039	mtspr	SPRN_DBAT0L,r10
1040	mtspr	SPRN_DBAT1U,r10
1041	mtspr	SPRN_DBAT1L,r10
1042	mtspr	SPRN_DBAT2U,r10
1043	mtspr	SPRN_DBAT2L,r10
1044	mtspr	SPRN_DBAT3U,r10
1045	mtspr	SPRN_DBAT3L,r10
1046	mtspr	SPRN_IBAT0U,r10
1047	mtspr	SPRN_IBAT0L,r10
1048	mtspr	SPRN_IBAT1U,r10
1049	mtspr	SPRN_IBAT1L,r10
1050	mtspr	SPRN_IBAT2U,r10
1051	mtspr	SPRN_IBAT2L,r10
1052	mtspr	SPRN_IBAT3U,r10
1053	mtspr	SPRN_IBAT3L,r10
1054BEGIN_MMU_FTR_SECTION
1055	/* Here's a tweak: at this point, CPU setup have
1056	 * not been called yet, so HIGH_BAT_EN may not be
1057	 * set in HID0 for the 745x processors. However, it
1058	 * seems that doesn't affect our ability to actually
1059	 * write to these SPRs.
1060	 */
1061	mtspr	SPRN_DBAT4U,r10
1062	mtspr	SPRN_DBAT4L,r10
1063	mtspr	SPRN_DBAT5U,r10
1064	mtspr	SPRN_DBAT5L,r10
1065	mtspr	SPRN_DBAT6U,r10
1066	mtspr	SPRN_DBAT6L,r10
1067	mtspr	SPRN_DBAT7U,r10
1068	mtspr	SPRN_DBAT7L,r10
1069	mtspr	SPRN_IBAT4U,r10
1070	mtspr	SPRN_IBAT4L,r10
1071	mtspr	SPRN_IBAT5U,r10
1072	mtspr	SPRN_IBAT5L,r10
1073	mtspr	SPRN_IBAT6U,r10
1074	mtspr	SPRN_IBAT6L,r10
1075	mtspr	SPRN_IBAT7U,r10
1076	mtspr	SPRN_IBAT7L,r10
1077END_MMU_FTR_SECTION_IFSET(MMU_FTR_USE_HIGH_BATS)
1078	blr
1079SYM_FUNC_END(clear_bats)
1080
1081_GLOBAL(update_bats)
1082	lis	r4, 1f@h
1083	ori	r4, r4, 1f@l
1084	tophys(r4, r4)
1085	mfmsr	r6
1086	mflr	r7
1087	li	r3, MSR_KERNEL & ~(MSR_IR | MSR_DR)
1088	rlwinm	r0, r6, 0, ~MSR_RI
1089	rlwinm	r0, r0, 0, ~MSR_EE
1090	mtmsr	r0
1091
1092	.align	4
1093	mtspr	SPRN_SRR0, r4
1094	mtspr	SPRN_SRR1, r3
1095	rfi
10961:	bl	clear_bats
1097	lis	r3, BATS@ha
1098	addi	r3, r3, BATS@l
1099	tophys(r3, r3)
1100	LOAD_BAT(0, r3, r4, r5)
1101	LOAD_BAT(1, r3, r4, r5)
1102	LOAD_BAT(2, r3, r4, r5)
1103	LOAD_BAT(3, r3, r4, r5)
1104BEGIN_MMU_FTR_SECTION
1105	LOAD_BAT(4, r3, r4, r5)
1106	LOAD_BAT(5, r3, r4, r5)
1107	LOAD_BAT(6, r3, r4, r5)
1108	LOAD_BAT(7, r3, r4, r5)
1109END_MMU_FTR_SECTION_IFSET(MMU_FTR_USE_HIGH_BATS)
1110	li	r3, MSR_KERNEL & ~(MSR_IR | MSR_DR | MSR_RI)
1111	mtmsr	r3
1112	mtspr	SPRN_SRR0, r7
1113	mtspr	SPRN_SRR1, r6
1114	rfi
1115
1116SYM_FUNC_START_LOCAL(flush_tlbs)
1117	lis	r10, 0x40
11181:	addic.	r10, r10, -0x1000
1119	tlbie	r10
1120	bgt	1b
1121	sync
1122	blr
1123SYM_FUNC_END(flush_tlbs)
1124
1125SYM_FUNC_START_LOCAL(mmu_off)
1126 	addi	r4, r3, __after_mmu_off - _start
1127	mfmsr	r3
1128	andi.	r0,r3,MSR_DR|MSR_IR		/* MMU enabled? */
1129	beqlr
1130	andc	r3,r3,r0
1131
1132	.align	4
1133	mtspr	SPRN_SRR0,r4
1134	mtspr	SPRN_SRR1,r3
1135	sync
1136	rfi
1137SYM_FUNC_END(mmu_off)
1138
1139/* We use one BAT to map up to 256M of RAM at _PAGE_OFFSET */
1140SYM_FUNC_START_LOCAL(initial_bats)
1141	lis	r11,PAGE_OFFSET@h
1142	tophys(r8,r11)
1143#ifdef CONFIG_SMP
1144	ori	r8,r8,0x12		/* R/W access, M=1 */
1145#else
1146	ori	r8,r8,2			/* R/W access */
1147#endif /* CONFIG_SMP */
1148	ori	r11,r11,BL_256M<<2|0x2	/* set up BAT registers for 604 */
1149
1150	mtspr	SPRN_DBAT0L,r8		/* N.B. 6xx have valid */
1151	mtspr	SPRN_DBAT0U,r11		/* bit in upper BAT register */
1152	mtspr	SPRN_IBAT0L,r8
1153	mtspr	SPRN_IBAT0U,r11
1154	isync
1155	blr
1156SYM_FUNC_END(initial_bats)
1157
1158#ifdef CONFIG_BOOTX_TEXT
1159SYM_FUNC_START_LOCAL(setup_disp_bat)
1160	/*
1161	 * setup the display bat prepared for us in prom.c
1162	 */
1163	mflr	r8
1164	bl	reloc_offset
1165	mtlr	r8
1166	addis	r8,r3,disp_BAT@ha
1167	addi	r8,r8,disp_BAT@l
1168	cmpwi	cr0,r8,0
1169	beqlr
1170	lwz	r11,0(r8)
1171	lwz	r8,4(r8)
1172	mtspr	SPRN_DBAT3L,r8
1173	mtspr	SPRN_DBAT3U,r11
1174	blr
1175SYM_FUNC_END(setup_disp_bat)
1176#endif /* CONFIG_BOOTX_TEXT */
1177
1178#ifdef CONFIG_PPC_EARLY_DEBUG_CPM
1179SYM_FUNC_START_LOCAL(setup_cpm_bat)
1180	lis	r8, 0xf000
1181	ori	r8, r8,	0x002a
1182	mtspr	SPRN_DBAT1L, r8
1183
1184	lis	r11, 0xf000
1185	ori	r11, r11, (BL_1M << 2) | 2
1186	mtspr	SPRN_DBAT1U, r11
1187
1188	blr
1189SYM_FUNC_END(setup_cpm_bat)
1190#endif
1191
1192#ifdef CONFIG_PPC_EARLY_DEBUG_USBGECKO
1193SYM_FUNC_START_LOCAL(setup_usbgecko_bat)
1194	/* prepare a BAT for early io */
1195#if defined(CONFIG_GAMECUBE)
1196	lis	r8, 0x0c00
1197#elif defined(CONFIG_WII)
1198	lis	r8, 0x0d00
1199#else
1200#error Invalid platform for USB Gecko based early debugging.
1201#endif
1202	/*
1203	 * The virtual address used must match the virtual address
1204	 * associated to the fixmap entry FIX_EARLY_DEBUG_BASE.
1205	 */
1206	lis	r11, 0xfffe	/* top 128K */
1207	ori	r8, r8, 0x002a	/* uncached, guarded ,rw */
1208	ori	r11, r11, 0x2	/* 128K, Vs=1, Vp=0 */
1209	mtspr	SPRN_DBAT1L, r8
1210	mtspr	SPRN_DBAT1U, r11
1211	blr
1212SYM_FUNC_END(setup_usbgecko_bat)
1213#endif
1214
1215	.data
1216