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