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 <asm/reg.h>
22#include <asm/page.h>
23#include <asm/mmu.h>
24#include <asm/cputable.h>
25#include <asm/cache.h>
26#include <asm/thread_info.h>
27#include <asm/ppc_asm.h>
28#include <asm/asm-offsets.h>
29#include <asm/ptrace.h>
30#include <asm/bug.h>
31#include <asm/kvm_book3s_asm.h>
32#include <asm/export.h>
33#include <asm/feature-fixups.h>
34
35#include "head_32.h"
36
37#define LOAD_BAT(n, reg, RA, RB)	\
38	/* see the comment for clear_bats() -- Cort */ \
39	li	RA,0;			\
40	mtspr	SPRN_IBAT##n##U,RA;	\
41	mtspr	SPRN_DBAT##n##U,RA;	\
42	lwz	RA,(n*16)+0(reg);	\
43	lwz	RB,(n*16)+4(reg);	\
44	mtspr	SPRN_IBAT##n##U,RA;	\
45	mtspr	SPRN_IBAT##n##L,RB;	\
46	lwz	RA,(n*16)+8(reg);	\
47	lwz	RB,(n*16)+12(reg);	\
48	mtspr	SPRN_DBAT##n##U,RA;	\
49	mtspr	SPRN_DBAT##n##L,RB
50
51	__HEAD
52	.stabs	"arch/powerpc/kernel/",N_SO,0,0,0f
53	.stabs	"head_book3s_32.S",N_SO,0,0,0f
540:
55_ENTRY(_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_ENTRY(_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_exception) when done.  */
242	EXCEPTION(0x100, Reset, unknown_exception, EXC_XFER_STD)
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	. = 0x200
259	DO_KVM  0x200
260MachineCheck:
261	EXCEPTION_PROLOG_0
262#ifdef CONFIG_PPC_CHRP
263	mfspr	r11, SPRN_SPRG_THREAD
264	lwz	r11, RTAS_SP(r11)
265	cmpwi	cr1, r11, 0
266	bne	cr1, 7f
267#endif /* CONFIG_PPC_CHRP */
268	EXCEPTION_PROLOG_1 for_rtas=1
2697:	EXCEPTION_PROLOG_2
270	addi	r3,r1,STACK_FRAME_OVERHEAD
271#ifdef CONFIG_PPC_CHRP
272#ifdef CONFIG_VMAP_STACK
273	mfspr	r4, SPRN_SPRG_THREAD
274	tovirt(r4, r4)
275	lwz	r4, RTAS_SP(r4)
276	cmpwi	cr1, r4, 0
277#endif
278	beq	cr1, machine_check_tramp
279	twi	31, 0, 0
280#else
281	b	machine_check_tramp
282#endif
283
284/* Data access exception. */
285	. = 0x300
286	DO_KVM  0x300
287DataAccess:
288#ifdef CONFIG_VMAP_STACK
289BEGIN_MMU_FTR_SECTION
290	mtspr	SPRN_SPRG_SCRATCH2,r10
291	mfspr	r10, SPRN_SPRG_THREAD
292	stw	r11, THR11(r10)
293	mfspr	r10, SPRN_DSISR
294	mfcr	r11
295	andis.	r10, r10, (DSISR_BAD_FAULT_32S | DSISR_DABRMATCH)@h
296	mfspr	r10, SPRN_SPRG_THREAD
297	beq	hash_page_dsi
298.Lhash_page_dsi_cont:
299	mtcr	r11
300	lwz	r11, THR11(r10)
301	mfspr	r10, SPRN_SPRG_SCRATCH2
302MMU_FTR_SECTION_ELSE
303	b	1f
304ALT_MMU_FTR_SECTION_END_IFSET(MMU_FTR_HPTE_TABLE)
3051:	EXCEPTION_PROLOG_0 handle_dar_dsisr=1
306	EXCEPTION_PROLOG_1
307	b	handle_page_fault_tramp_1
308#else	/* CONFIG_VMAP_STACK */
309	EXCEPTION_PROLOG handle_dar_dsisr=1
310	get_and_save_dar_dsisr_on_stack	r4, r5, r11
311BEGIN_MMU_FTR_SECTION
312	andis.	r0, r5, (DSISR_BAD_FAULT_32S | DSISR_DABRMATCH)@h
313	bne	handle_page_fault_tramp_2	/* if not, try to put a PTE */
314	rlwinm	r3, r5, 32 - 15, 21, 21		/* DSISR_STORE -> _PAGE_RW */
315	bl	hash_page
316	b	handle_page_fault_tramp_1
317MMU_FTR_SECTION_ELSE
318	b	handle_page_fault_tramp_2
319ALT_MMU_FTR_SECTION_END_IFSET(MMU_FTR_HPTE_TABLE)
320#endif	/* CONFIG_VMAP_STACK */
321
322/* Instruction access exception. */
323	. = 0x400
324	DO_KVM  0x400
325InstructionAccess:
326#ifdef CONFIG_VMAP_STACK
327	mtspr	SPRN_SPRG_SCRATCH0,r10
328	mtspr	SPRN_SPRG_SCRATCH1,r11
329	mfspr	r10, SPRN_SPRG_THREAD
330	mfspr	r11, SPRN_SRR0
331	stw	r11, SRR0(r10)
332	mfspr	r11, SPRN_SRR1		/* check whether user or kernel */
333	stw	r11, SRR1(r10)
334	mfcr	r10
335BEGIN_MMU_FTR_SECTION
336	andis.	r11, r11, SRR1_ISI_NOPT@h	/* no pte found? */
337	bne	hash_page_isi
338.Lhash_page_isi_cont:
339	mfspr	r11, SPRN_SRR1		/* check whether user or kernel */
340END_MMU_FTR_SECTION_IFSET(MMU_FTR_HPTE_TABLE)
341	andi.	r11, r11, MSR_PR
342
343	EXCEPTION_PROLOG_1
344	EXCEPTION_PROLOG_2
345#else	/* CONFIG_VMAP_STACK */
346	EXCEPTION_PROLOG
347	andis.	r0,r9,SRR1_ISI_NOPT@h	/* no pte found? */
348	beq	1f			/* if so, try to put a PTE */
349	li	r3,0			/* into the hash table */
350	mr	r4,r12			/* SRR0 is fault address */
351BEGIN_MMU_FTR_SECTION
352	bl	hash_page
353END_MMU_FTR_SECTION_IFSET(MMU_FTR_HPTE_TABLE)
354#endif	/* CONFIG_VMAP_STACK */
3551:	mr	r4,r12
356	andis.	r5,r9,DSISR_SRR1_MATCH_32S@h /* Filter relevant SRR1 bits */
357	stw	r4, _DAR(r11)
358	EXC_XFER_LITE(0x400, handle_page_fault)
359
360/* External interrupt */
361	EXCEPTION(0x500, HardwareInterrupt, do_IRQ, EXC_XFER_LITE)
362
363/* Alignment exception */
364	. = 0x600
365	DO_KVM  0x600
366Alignment:
367	EXCEPTION_PROLOG handle_dar_dsisr=1
368	save_dar_dsisr_on_stack r4, r5, r11
369	addi	r3,r1,STACK_FRAME_OVERHEAD
370	b	alignment_exception_tramp
371
372/* Program check exception */
373	EXCEPTION(0x700, ProgramCheck, program_check_exception, EXC_XFER_STD)
374
375/* Floating-point unavailable */
376	. = 0x800
377	DO_KVM  0x800
378FPUnavailable:
379#ifdef CONFIG_PPC_FPU
380BEGIN_FTR_SECTION
381/*
382 * Certain Freescale cores don't have a FPU and treat fp instructions
383 * as a FP Unavailable exception.  Redirect to illegal/emulation handling.
384 */
385	b 	ProgramCheck
386END_FTR_SECTION_IFSET(CPU_FTR_FPU_UNAVAILABLE)
387	EXCEPTION_PROLOG
388	beq	1f
389	bl	load_up_fpu		/* if from user, just load it up */
390	b	fast_exception_return
3911:	addi	r3,r1,STACK_FRAME_OVERHEAD
392	EXC_XFER_LITE(0x800, kernel_fp_unavailable_exception)
393#else
394	b 	ProgramCheck
395#endif
396
397/* Decrementer */
398	EXCEPTION(0x900, Decrementer, timer_interrupt, EXC_XFER_LITE)
399
400	EXCEPTION(0xa00, Trap_0a, unknown_exception, EXC_XFER_STD)
401	EXCEPTION(0xb00, Trap_0b, unknown_exception, EXC_XFER_STD)
402
403/* System call */
404	. = 0xc00
405	DO_KVM  0xc00
406SystemCall:
407	SYSCALL_ENTRY	0xc00
408
409	EXCEPTION(0xd00, SingleStep, single_step_exception, EXC_XFER_STD)
410	EXCEPTION(0xe00, Trap_0e, unknown_exception, EXC_XFER_STD)
411
412/*
413 * The Altivec unavailable trap is at 0x0f20.  Foo.
414 * We effectively remap it to 0x3000.
415 * We include an altivec unavailable exception vector even if
416 * not configured for Altivec, so that you can't panic a
417 * non-altivec kernel running on a machine with altivec just
418 * by executing an altivec instruction.
419 */
420	. = 0xf00
421	DO_KVM  0xf00
422	b	PerformanceMonitor
423
424	. = 0xf20
425	DO_KVM  0xf20
426	b	AltiVecUnavailable
427
428/*
429 * Handle TLB miss for instruction on 603/603e.
430 * Note: we get an alternate set of r0 - r3 to use automatically.
431 */
432	. = 0x1000
433InstructionTLBMiss:
434/*
435 * r0:	scratch
436 * r1:	linux style pte ( later becomes ppc hardware pte )
437 * r2:	ptr to linux-style pte
438 * r3:	scratch
439 */
440	/* Get PTE (linux-style) and check access */
441	mfspr	r3,SPRN_IMISS
442#ifdef CONFIG_MODULES
443	lis	r1, TASK_SIZE@h		/* check if kernel address */
444	cmplw	0,r1,r3
445#endif
446	mfspr	r2, SPRN_SDR1
447	li	r1,_PAGE_PRESENT | _PAGE_ACCESSED | _PAGE_EXEC
448	rlwinm	r2, r2, 28, 0xfffff000
449#ifdef CONFIG_MODULES
450	bgt-	112f
451	lis	r2, (swapper_pg_dir - PAGE_OFFSET)@ha	/* if kernel address, use */
452	addi	r2, r2, (swapper_pg_dir - PAGE_OFFSET)@l	/* kernel page table */
453#endif
454112:	rlwimi	r2,r3,12,20,29		/* insert top 10 bits of address */
455	lwz	r2,0(r2)		/* get pmd entry */
456	rlwinm.	r2,r2,0,0,19		/* extract address of pte page */
457	beq-	InstructionAddressInvalid	/* return if no mapping */
458	rlwimi	r2,r3,22,20,29		/* insert next 10 bits of address */
459	lwz	r0,0(r2)		/* get linux-style pte */
460	andc.	r1,r1,r0		/* check access & ~permission */
461	bne-	InstructionAddressInvalid /* return if access not permitted */
462	/* Convert linux-style PTE to low word of PPC-style PTE */
463	rlwimi	r0,r0,32-2,31,31	/* _PAGE_USER -> PP lsb */
464	ori	r1, r1, 0xe06		/* clear out reserved bits */
465	andc	r1, r0, r1		/* PP = user? 1 : 0 */
466BEGIN_FTR_SECTION
467	rlwinm	r1,r1,0,~_PAGE_COHERENT	/* clear M (coherence not required) */
468END_FTR_SECTION_IFCLR(CPU_FTR_NEED_COHERENT)
469	mtspr	SPRN_RPA,r1
470	tlbli	r3
471	mfspr	r3,SPRN_SRR1		/* Need to restore CR0 */
472	mtcrf	0x80,r3
473	rfi
474InstructionAddressInvalid:
475	mfspr	r3,SPRN_SRR1
476	rlwinm	r1,r3,9,6,6	/* Get load/store bit */
477
478	addis	r1,r1,0x2000
479	mtspr	SPRN_DSISR,r1	/* (shouldn't be needed) */
480	andi.	r2,r3,0xFFFF	/* Clear upper bits of SRR1 */
481	or	r2,r2,r1
482	mtspr	SPRN_SRR1,r2
483	mfspr	r1,SPRN_IMISS	/* Get failing address */
484	rlwinm.	r2,r2,0,31,31	/* Check for little endian access */
485	rlwimi	r2,r2,1,30,30	/* change 1 -> 3 */
486	xor	r1,r1,r2
487	mtspr	SPRN_DAR,r1	/* Set fault address */
488	mfmsr	r0		/* Restore "normal" registers */
489	xoris	r0,r0,MSR_TGPR>>16
490	mtcrf	0x80,r3		/* Restore CR0 */
491	mtmsr	r0
492	b	InstructionAccess
493
494/*
495 * Handle TLB miss for DATA Load operation on 603/603e
496 */
497	. = 0x1100
498DataLoadTLBMiss:
499/*
500 * r0:	scratch
501 * r1:	linux style pte ( later becomes ppc hardware pte )
502 * r2:	ptr to linux-style pte
503 * r3:	scratch
504 */
505	/* Get PTE (linux-style) and check access */
506	mfspr	r3,SPRN_DMISS
507	lis	r1, TASK_SIZE@h		/* check if kernel address */
508	cmplw	0,r1,r3
509	mfspr	r2, SPRN_SDR1
510	li	r1, _PAGE_PRESENT | _PAGE_ACCESSED
511	rlwinm	r2, r2, 28, 0xfffff000
512	bgt-	112f
513	lis	r2, (swapper_pg_dir - PAGE_OFFSET)@ha	/* if kernel address, use */
514	addi	r2, r2, (swapper_pg_dir - PAGE_OFFSET)@l	/* kernel page table */
515112:	rlwimi	r2,r3,12,20,29		/* insert top 10 bits of address */
516	lwz	r2,0(r2)		/* get pmd entry */
517	rlwinm.	r2,r2,0,0,19		/* extract address of pte page */
518	beq-	DataAddressInvalid	/* return if no mapping */
519	rlwimi	r2,r3,22,20,29		/* insert next 10 bits of address */
520	lwz	r0,0(r2)		/* get linux-style pte */
521	andc.	r1,r1,r0		/* check access & ~permission */
522	bne-	DataAddressInvalid	/* return if access not permitted */
523	/*
524	 * NOTE! We are assuming this is not an SMP system, otherwise
525	 * we would need to update the pte atomically with lwarx/stwcx.
526	 */
527	/* Convert linux-style PTE to low word of PPC-style PTE */
528	rlwinm	r1,r0,32-9,30,30	/* _PAGE_RW -> PP msb */
529	rlwimi	r0,r0,32-1,30,30	/* _PAGE_USER -> PP msb */
530	rlwimi	r0,r0,32-1,31,31	/* _PAGE_USER -> PP lsb */
531	ori	r1,r1,0xe04		/* clear out reserved bits */
532	andc	r1,r0,r1		/* PP = user? rw? 1: 3: 0 */
533BEGIN_FTR_SECTION
534	rlwinm	r1,r1,0,~_PAGE_COHERENT	/* clear M (coherence not required) */
535END_FTR_SECTION_IFCLR(CPU_FTR_NEED_COHERENT)
536	mtspr	SPRN_RPA,r1
537	mfspr	r2,SPRN_SRR1		/* Need to restore CR0 */
538	mtcrf	0x80,r2
539BEGIN_MMU_FTR_SECTION
540	li	r0,1
541	mfspr	r1,SPRN_SPRG_603_LRU
542	rlwinm	r2,r3,20,27,31		/* Get Address bits 15:19 */
543	slw	r0,r0,r2
544	xor	r1,r0,r1
545	srw	r0,r1,r2
546	mtspr   SPRN_SPRG_603_LRU,r1
547	mfspr	r2,SPRN_SRR1
548	rlwimi	r2,r0,31-14,14,14
549	mtspr   SPRN_SRR1,r2
550END_MMU_FTR_SECTION_IFSET(MMU_FTR_NEED_DTLB_SW_LRU)
551	tlbld	r3
552	rfi
553DataAddressInvalid:
554	mfspr	r3,SPRN_SRR1
555	rlwinm	r1,r3,9,6,6	/* Get load/store bit */
556	addis	r1,r1,0x2000
557	mtspr	SPRN_DSISR,r1
558	andi.	r2,r3,0xFFFF	/* Clear upper bits of SRR1 */
559	mtspr	SPRN_SRR1,r2
560	mfspr	r1,SPRN_DMISS	/* Get failing address */
561	rlwinm.	r2,r2,0,31,31	/* Check for little endian access */
562	beq	20f		/* Jump if big endian */
563	xori	r1,r1,3
56420:	mtspr	SPRN_DAR,r1	/* Set fault address */
565	mfmsr	r0		/* Restore "normal" registers */
566	xoris	r0,r0,MSR_TGPR>>16
567	mtcrf	0x80,r3		/* Restore CR0 */
568	mtmsr	r0
569	b	DataAccess
570
571/*
572 * Handle TLB miss for DATA Store on 603/603e
573 */
574	. = 0x1200
575DataStoreTLBMiss:
576/*
577 * r0:	scratch
578 * r1:	linux style pte ( later becomes ppc hardware pte )
579 * r2:	ptr to linux-style pte
580 * r3:	scratch
581 */
582	/* Get PTE (linux-style) and check access */
583	mfspr	r3,SPRN_DMISS
584	lis	r1, TASK_SIZE@h		/* check if kernel address */
585	cmplw	0,r1,r3
586	mfspr	r2, SPRN_SDR1
587	li	r1, _PAGE_RW | _PAGE_DIRTY | _PAGE_PRESENT | _PAGE_ACCESSED
588	rlwinm	r2, r2, 28, 0xfffff000
589	bgt-	112f
590	lis	r2, (swapper_pg_dir - PAGE_OFFSET)@ha	/* if kernel address, use */
591	addi	r2, r2, (swapper_pg_dir - PAGE_OFFSET)@l	/* kernel page table */
592112:	rlwimi	r2,r3,12,20,29		/* insert top 10 bits of address */
593	lwz	r2,0(r2)		/* get pmd entry */
594	rlwinm.	r2,r2,0,0,19		/* extract address of pte page */
595	beq-	DataAddressInvalid	/* return if no mapping */
596	rlwimi	r2,r3,22,20,29		/* insert next 10 bits of address */
597	lwz	r0,0(r2)		/* get linux-style pte */
598	andc.	r1,r1,r0		/* check access & ~permission */
599	bne-	DataAddressInvalid	/* return if access not permitted */
600	/*
601	 * NOTE! We are assuming this is not an SMP system, otherwise
602	 * we would need to update the pte atomically with lwarx/stwcx.
603	 */
604	/* Convert linux-style PTE to low word of PPC-style PTE */
605	rlwimi	r0,r0,32-2,31,31	/* _PAGE_USER -> PP lsb */
606	li	r1,0xe06		/* clear out reserved bits & PP msb */
607	andc	r1,r0,r1		/* PP = user? 1: 0 */
608BEGIN_FTR_SECTION
609	rlwinm	r1,r1,0,~_PAGE_COHERENT	/* clear M (coherence not required) */
610END_FTR_SECTION_IFCLR(CPU_FTR_NEED_COHERENT)
611	mtspr	SPRN_RPA,r1
612	mfspr	r2,SPRN_SRR1		/* Need to restore CR0 */
613	mtcrf	0x80,r2
614BEGIN_MMU_FTR_SECTION
615	li	r0,1
616	mfspr	r1,SPRN_SPRG_603_LRU
617	rlwinm	r2,r3,20,27,31		/* Get Address bits 15:19 */
618	slw	r0,r0,r2
619	xor	r1,r0,r1
620	srw	r0,r1,r2
621	mtspr   SPRN_SPRG_603_LRU,r1
622	mfspr	r2,SPRN_SRR1
623	rlwimi	r2,r0,31-14,14,14
624	mtspr   SPRN_SRR1,r2
625END_MMU_FTR_SECTION_IFSET(MMU_FTR_NEED_DTLB_SW_LRU)
626	tlbld	r3
627	rfi
628
629#ifndef CONFIG_ALTIVEC
630#define altivec_assist_exception	unknown_exception
631#endif
632
633#ifndef CONFIG_TAU_INT
634#define TAUException	unknown_exception
635#endif
636
637	EXCEPTION(0x1300, Trap_13, instruction_breakpoint_exception, EXC_XFER_STD)
638	EXCEPTION(0x1400, SMI, SMIException, EXC_XFER_STD)
639	EXCEPTION(0x1500, Trap_15, unknown_exception, EXC_XFER_STD)
640	EXCEPTION(0x1600, Trap_16, altivec_assist_exception, EXC_XFER_STD)
641	EXCEPTION(0x1700, Trap_17, TAUException, EXC_XFER_STD)
642	EXCEPTION(0x1800, Trap_18, unknown_exception, EXC_XFER_STD)
643	EXCEPTION(0x1900, Trap_19, unknown_exception, EXC_XFER_STD)
644	EXCEPTION(0x1a00, Trap_1a, unknown_exception, EXC_XFER_STD)
645	EXCEPTION(0x1b00, Trap_1b, unknown_exception, EXC_XFER_STD)
646	EXCEPTION(0x1c00, Trap_1c, unknown_exception, EXC_XFER_STD)
647	EXCEPTION(0x1d00, Trap_1d, unknown_exception, EXC_XFER_STD)
648	EXCEPTION(0x1e00, Trap_1e, unknown_exception, EXC_XFER_STD)
649	EXCEPTION(0x1f00, Trap_1f, unknown_exception, EXC_XFER_STD)
650	EXCEPTION(0x2000, RunMode, RunModeException, EXC_XFER_STD)
651	EXCEPTION(0x2100, Trap_21, unknown_exception, EXC_XFER_STD)
652	EXCEPTION(0x2200, Trap_22, unknown_exception, EXC_XFER_STD)
653	EXCEPTION(0x2300, Trap_23, unknown_exception, EXC_XFER_STD)
654	EXCEPTION(0x2400, Trap_24, unknown_exception, EXC_XFER_STD)
655	EXCEPTION(0x2500, Trap_25, unknown_exception, EXC_XFER_STD)
656	EXCEPTION(0x2600, Trap_26, unknown_exception, EXC_XFER_STD)
657	EXCEPTION(0x2700, Trap_27, unknown_exception, EXC_XFER_STD)
658	EXCEPTION(0x2800, Trap_28, unknown_exception, EXC_XFER_STD)
659	EXCEPTION(0x2900, Trap_29, unknown_exception, EXC_XFER_STD)
660	EXCEPTION(0x2a00, Trap_2a, unknown_exception, EXC_XFER_STD)
661	EXCEPTION(0x2b00, Trap_2b, unknown_exception, EXC_XFER_STD)
662	EXCEPTION(0x2c00, Trap_2c, unknown_exception, EXC_XFER_STD)
663	EXCEPTION(0x2d00, Trap_2d, unknown_exception, EXC_XFER_STD)
664	EXCEPTION(0x2e00, Trap_2e, unknown_exception, EXC_XFER_STD)
665	EXCEPTION(0x2f00, Trap_2f, unknown_exception, EXC_XFER_STD)
666
667	. = 0x3000
668
669machine_check_tramp:
670	EXC_XFER_STD(0x200, machine_check_exception)
671
672alignment_exception_tramp:
673	EXC_XFER_STD(0x600, alignment_exception)
674
675handle_page_fault_tramp_1:
676#ifdef CONFIG_VMAP_STACK
677	EXCEPTION_PROLOG_2 handle_dar_dsisr=1
678#endif
679	lwz	r4, _DAR(r11)
680	lwz	r5, _DSISR(r11)
681	/* fall through */
682handle_page_fault_tramp_2:
683	EXC_XFER_LITE(0x300, handle_page_fault)
684
685#ifdef CONFIG_VMAP_STACK
686.macro save_regs_thread		thread
687	stw	r0, THR0(\thread)
688	stw	r3, THR3(\thread)
689	stw	r4, THR4(\thread)
690	stw	r5, THR5(\thread)
691	stw	r6, THR6(\thread)
692	stw	r8, THR8(\thread)
693	stw	r9, THR9(\thread)
694	mflr	r0
695	stw	r0, THLR(\thread)
696	mfctr	r0
697	stw	r0, THCTR(\thread)
698.endm
699
700.macro restore_regs_thread	thread
701	lwz	r0, THLR(\thread)
702	mtlr	r0
703	lwz	r0, THCTR(\thread)
704	mtctr	r0
705	lwz	r0, THR0(\thread)
706	lwz	r3, THR3(\thread)
707	lwz	r4, THR4(\thread)
708	lwz	r5, THR5(\thread)
709	lwz	r6, THR6(\thread)
710	lwz	r8, THR8(\thread)
711	lwz	r9, THR9(\thread)
712.endm
713
714hash_page_dsi:
715	save_regs_thread	r10
716	mfdsisr	r3
717	mfdar	r4
718	mfsrr0	r5
719	mfsrr1	r9
720	rlwinm	r3, r3, 32 - 15, _PAGE_RW	/* DSISR_STORE -> _PAGE_RW */
721	bl	hash_page
722	mfspr	r10, SPRN_SPRG_THREAD
723	restore_regs_thread r10
724	b	.Lhash_page_dsi_cont
725
726hash_page_isi:
727	mr	r11, r10
728	mfspr	r10, SPRN_SPRG_THREAD
729	save_regs_thread	r10
730	li	r3, 0
731	lwz	r4, SRR0(r10)
732	lwz	r9, SRR1(r10)
733	bl	hash_page
734	mfspr	r10, SPRN_SPRG_THREAD
735	restore_regs_thread r10
736	mr	r10, r11
737	b	.Lhash_page_isi_cont
738
739	.globl fast_hash_page_return
740fast_hash_page_return:
741	andis.	r10, r9, SRR1_ISI_NOPT@h	/* Set on ISI, cleared on DSI */
742	mfspr	r10, SPRN_SPRG_THREAD
743	restore_regs_thread r10
744	bne	1f
745
746	/* DSI */
747	mtcr	r11
748	lwz	r11, THR11(r10)
749	mfspr	r10, SPRN_SPRG_SCRATCH2
750	rfi
751
7521:	/* ISI */
753	mtcr	r11
754	mfspr	r11, SPRN_SPRG_SCRATCH1
755	mfspr	r10, SPRN_SPRG_SCRATCH0
756	rfi
757
758stack_overflow:
759	vmap_stack_overflow_exception
760#endif
761
762AltiVecUnavailable:
763	EXCEPTION_PROLOG
764#ifdef CONFIG_ALTIVEC
765	beq	1f
766	bl	load_up_altivec		/* if from user, just load it up */
767	b	fast_exception_return
768#endif /* CONFIG_ALTIVEC */
7691:	addi	r3,r1,STACK_FRAME_OVERHEAD
770	EXC_XFER_LITE(0xf20, altivec_unavailable_exception)
771
772PerformanceMonitor:
773	EXCEPTION_PROLOG
774	addi	r3,r1,STACK_FRAME_OVERHEAD
775	EXC_XFER_STD(0xf00, performance_monitor_exception)
776
777
778/*
779 * This code is jumped to from the startup code to copy
780 * the kernel image to physical address PHYSICAL_START.
781 */
782relocate_kernel:
783	addis	r9,r26,klimit@ha	/* fetch klimit */
784	lwz	r25,klimit@l(r9)
785	addis	r25,r25,-KERNELBASE@h
786	lis	r3,PHYSICAL_START@h	/* Destination base address */
787	li	r6,0			/* Destination offset */
788	li	r5,0x4000		/* # bytes of memory to copy */
789	bl	copy_and_flush		/* copy the first 0x4000 bytes */
790	addi	r0,r3,4f@l		/* jump to the address of 4f */
791	mtctr	r0			/* in copy and do the rest. */
792	bctr				/* jump to the copy */
7934:	mr	r5,r25
794	bl	copy_and_flush		/* copy the rest */
795	b	turn_on_mmu
796
797/*
798 * Copy routine used to copy the kernel to start at physical address 0
799 * and flush and invalidate the caches as needed.
800 * r3 = dest addr, r4 = source addr, r5 = copy limit, r6 = start offset
801 * on exit, r3, r4, r5 are unchanged, r6 is updated to be >= r5.
802 */
803_ENTRY(copy_and_flush)
804	addi	r5,r5,-4
805	addi	r6,r6,-4
8064:	li	r0,L1_CACHE_BYTES/4
807	mtctr	r0
8083:	addi	r6,r6,4			/* copy a cache line */
809	lwzx	r0,r6,r4
810	stwx	r0,r6,r3
811	bdnz	3b
812	dcbst	r6,r3			/* write it to memory */
813	sync
814	icbi	r6,r3			/* flush the icache line */
815	cmplw	0,r6,r5
816	blt	4b
817	sync				/* additional sync needed on g4 */
818	isync
819	addi	r5,r5,4
820	addi	r6,r6,4
821	blr
822
823#ifdef CONFIG_SMP
824	.globl __secondary_start_mpc86xx
825__secondary_start_mpc86xx:
826	mfspr	r3, SPRN_PIR
827	stw	r3, __secondary_hold_acknowledge@l(0)
828	mr	r24, r3			/* cpu # */
829	b	__secondary_start
830
831	.globl	__secondary_start_pmac_0
832__secondary_start_pmac_0:
833	/* NB the entries for cpus 0, 1, 2 must each occupy 8 bytes. */
834	li	r24,0
835	b	1f
836	li	r24,1
837	b	1f
838	li	r24,2
839	b	1f
840	li	r24,3
8411:
842	/* on powersurge, we come in here with IR=0 and DR=1, and DBAT 0
843	   set to map the 0xf0000000 - 0xffffffff region */
844	mfmsr	r0
845	rlwinm	r0,r0,0,28,26		/* clear DR (0x10) */
846	mtmsr	r0
847	isync
848
849	.globl	__secondary_start
850__secondary_start:
851	/* Copy some CPU settings from CPU 0 */
852	bl	__restore_cpu_setup
853
854	lis	r3,-KERNELBASE@h
855	mr	r4,r24
856	bl	call_setup_cpu		/* Call setup_cpu for this CPU */
857	lis	r3,-KERNELBASE@h
858	bl	init_idle_6xx
859
860	/* get current's stack and current */
861	lis	r2,secondary_current@ha
862	tophys(r2,r2)
863	lwz	r2,secondary_current@l(r2)
864	tophys(r1,r2)
865	lwz	r1,TASK_STACK(r1)
866
867	/* stack */
868	addi	r1,r1,THREAD_SIZE-STACK_FRAME_OVERHEAD
869	li	r0,0
870	tophys(r3,r1)
871	stw	r0,0(r3)
872
873	/* load up the MMU */
874	bl	load_segment_registers
875	bl	load_up_mmu
876
877	/* ptr to phys current thread */
878	tophys(r4,r2)
879	addi	r4,r4,THREAD	/* phys address of our thread_struct */
880	mtspr	SPRN_SPRG_THREAD,r4
881BEGIN_MMU_FTR_SECTION
882	lis	r4, (swapper_pg_dir - PAGE_OFFSET)@h
883	ori	r4, r4, (swapper_pg_dir - PAGE_OFFSET)@l
884	rlwinm	r4, r4, 4, 0xffff01ff
885	mtspr	SPRN_SDR1, r4
886END_MMU_FTR_SECTION_IFCLR(MMU_FTR_HPTE_TABLE)
887
888	/* enable MMU and jump to start_secondary */
889	li	r4,MSR_KERNEL
890	lis	r3,start_secondary@h
891	ori	r3,r3,start_secondary@l
892	mtspr	SPRN_SRR0,r3
893	mtspr	SPRN_SRR1,r4
894	rfi
895#endif /* CONFIG_SMP */
896
897#ifdef CONFIG_KVM_BOOK3S_HANDLER
898#include "../kvm/book3s_rmhandlers.S"
899#endif
900
901/*
902 * Load stuff into the MMU.  Intended to be called with
903 * IR=0 and DR=0.
904 */
905early_hash_table:
906	sync			/* Force all PTE updates to finish */
907	isync
908	tlbia			/* Clear all TLB entries */
909	sync			/* wait for tlbia/tlbie to finish */
910	TLBSYNC			/* ... on all CPUs */
911	/* Load the SDR1 register (hash table base & size) */
912	lis	r6, early_hash - PAGE_OFFSET@h
913	ori	r6, r6, 3	/* 256kB table */
914	mtspr	SPRN_SDR1, r6
915	blr
916
917load_up_mmu:
918	sync			/* Force all PTE updates to finish */
919	isync
920	tlbia			/* Clear all TLB entries */
921	sync			/* wait for tlbia/tlbie to finish */
922	TLBSYNC			/* ... on all CPUs */
923BEGIN_MMU_FTR_SECTION
924	/* Load the SDR1 register (hash table base & size) */
925	lis	r6,_SDR1@ha
926	tophys(r6,r6)
927	lwz	r6,_SDR1@l(r6)
928	mtspr	SPRN_SDR1,r6
929END_MMU_FTR_SECTION_IFSET(MMU_FTR_HPTE_TABLE)
930
931/* Load the BAT registers with the values set up by MMU_init. */
932	lis	r3,BATS@ha
933	addi	r3,r3,BATS@l
934	tophys(r3,r3)
935	LOAD_BAT(0,r3,r4,r5)
936	LOAD_BAT(1,r3,r4,r5)
937	LOAD_BAT(2,r3,r4,r5)
938	LOAD_BAT(3,r3,r4,r5)
939BEGIN_MMU_FTR_SECTION
940	LOAD_BAT(4,r3,r4,r5)
941	LOAD_BAT(5,r3,r4,r5)
942	LOAD_BAT(6,r3,r4,r5)
943	LOAD_BAT(7,r3,r4,r5)
944END_MMU_FTR_SECTION_IFSET(MMU_FTR_USE_HIGH_BATS)
945	blr
946
947_GLOBAL(load_segment_registers)
948	li	r0, NUM_USER_SEGMENTS /* load up user segment register values */
949	mtctr	r0		/* for context 0 */
950	li	r3, 0		/* Kp = 0, Ks = 0, VSID = 0 */
951#ifdef CONFIG_PPC_KUEP
952	oris	r3, r3, SR_NX@h	/* Set Nx */
953#endif
954#ifdef CONFIG_PPC_KUAP
955	oris	r3, r3, SR_KS@h	/* Set Ks */
956#endif
957	li	r4, 0
9583:	mtsrin	r3, r4
959	addi	r3, r3, 0x111	/* increment VSID */
960	addis	r4, r4, 0x1000	/* address of next segment */
961	bdnz	3b
962	li	r0, 16 - NUM_USER_SEGMENTS /* load up kernel segment registers */
963	mtctr	r0			/* for context 0 */
964	rlwinm	r3, r3, 0, ~SR_NX	/* Nx = 0 */
965	rlwinm	r3, r3, 0, ~SR_KS	/* Ks = 0 */
966	oris	r3, r3, SR_KP@h		/* Kp = 1 */
9673:	mtsrin	r3, r4
968	addi	r3, r3, 0x111	/* increment VSID */
969	addis	r4, r4, 0x1000	/* address of next segment */
970	bdnz	3b
971	blr
972
973/*
974 * This is where the main kernel code starts.
975 */
976start_here:
977	/* ptr to current */
978	lis	r2,init_task@h
979	ori	r2,r2,init_task@l
980	/* Set up for using our exception vectors */
981	/* ptr to phys current thread */
982	tophys(r4,r2)
983	addi	r4,r4,THREAD	/* init task's THREAD */
984	mtspr	SPRN_SPRG_THREAD,r4
985BEGIN_MMU_FTR_SECTION
986	lis	r4, (swapper_pg_dir - PAGE_OFFSET)@h
987	ori	r4, r4, (swapper_pg_dir - PAGE_OFFSET)@l
988	rlwinm	r4, r4, 4, 0xffff01ff
989	mtspr	SPRN_SDR1, r4
990END_MMU_FTR_SECTION_IFCLR(MMU_FTR_HPTE_TABLE)
991
992	/* stack */
993	lis	r1,init_thread_union@ha
994	addi	r1,r1,init_thread_union@l
995	li	r0,0
996	stwu	r0,THREAD_SIZE-STACK_FRAME_OVERHEAD(r1)
997/*
998 * Do early platform-specific initialization,
999 * and set up the MMU.
1000 */
1001#ifdef CONFIG_KASAN
1002	bl	kasan_early_init
1003#endif
1004	li	r3,0
1005	mr	r4,r31
1006	bl	machine_init
1007	bl	__save_cpu_setup
1008	bl	MMU_init
1009	bl	MMU_init_hw_patch
1010
1011/*
1012 * Go back to running unmapped so we can load up new values
1013 * for SDR1 (hash table pointer) and the segment registers
1014 * and change to using our exception vectors.
1015 */
1016	lis	r4,2f@h
1017	ori	r4,r4,2f@l
1018	tophys(r4,r4)
1019	li	r3,MSR_KERNEL & ~(MSR_IR|MSR_DR)
1020
1021	.align	4
1022	mtspr	SPRN_SRR0,r4
1023	mtspr	SPRN_SRR1,r3
1024	rfi
1025/* Load up the kernel context */
10262:	bl	load_up_mmu
1027
1028#ifdef CONFIG_BDI_SWITCH
1029	/* Add helper information for the Abatron bdiGDB debugger.
1030	 * We do this here because we know the mmu is disabled, and
1031	 * will be enabled for real in just a few instructions.
1032	 */
1033	lis	r5, abatron_pteptrs@h
1034	ori	r5, r5, abatron_pteptrs@l
1035	stw	r5, 0xf0(0)	/* This much match your Abatron config */
1036	lis	r6, swapper_pg_dir@h
1037	ori	r6, r6, swapper_pg_dir@l
1038	tophys(r5, r5)
1039	stw	r6, 0(r5)
1040#endif /* CONFIG_BDI_SWITCH */
1041
1042/* Now turn on the MMU for real! */
1043	li	r4,MSR_KERNEL
1044	lis	r3,start_kernel@h
1045	ori	r3,r3,start_kernel@l
1046	mtspr	SPRN_SRR0,r3
1047	mtspr	SPRN_SRR1,r4
1048	rfi
1049
1050/*
1051 * void switch_mmu_context(struct mm_struct *prev, struct mm_struct *next);
1052 *
1053 * Set up the segment registers for a new context.
1054 */
1055_ENTRY(switch_mmu_context)
1056	lwz	r3,MMCONTEXTID(r4)
1057	cmpwi	cr0,r3,0
1058	blt-	4f
1059	mulli	r3,r3,897	/* multiply context by skew factor */
1060	rlwinm	r3,r3,4,8,27	/* VSID = (context & 0xfffff) << 4 */
1061#ifdef CONFIG_PPC_KUEP
1062	oris	r3, r3, SR_NX@h	/* Set Nx */
1063#endif
1064#ifdef CONFIG_PPC_KUAP
1065	oris	r3, r3, SR_KS@h	/* Set Ks */
1066#endif
1067	li	r0,NUM_USER_SEGMENTS
1068	mtctr	r0
1069
1070#ifdef CONFIG_BDI_SWITCH
1071	/* Context switch the PTE pointer for the Abatron BDI2000.
1072	 * The PGDIR is passed as second argument.
1073	 */
1074	lwz	r4, MM_PGD(r4)
1075	lis	r5, abatron_pteptrs@ha
1076	stw	r4, abatron_pteptrs@l + 0x4(r5)
1077#endif
1078BEGIN_MMU_FTR_SECTION
1079#ifndef CONFIG_BDI_SWITCH
1080	lwz	r4, MM_PGD(r4)
1081#endif
1082	tophys(r4, r4)
1083	rlwinm	r4, r4, 4, 0xffff01ff
1084	mtspr	SPRN_SDR1, r4
1085END_MMU_FTR_SECTION_IFCLR(MMU_FTR_HPTE_TABLE)
1086	li	r4,0
1087	isync
10883:
1089	mtsrin	r3,r4
1090	addi	r3,r3,0x111	/* next VSID */
1091	rlwinm	r3,r3,0,8,3	/* clear out any overflow from VSID field */
1092	addis	r4,r4,0x1000	/* address of next segment */
1093	bdnz	3b
1094	sync
1095	isync
1096	blr
10974:	trap
1098	EMIT_BUG_ENTRY 4b,__FILE__,__LINE__,0
1099	blr
1100EXPORT_SYMBOL(switch_mmu_context)
1101
1102/*
1103 * An undocumented "feature" of 604e requires that the v bit
1104 * be cleared before changing BAT values.
1105 *
1106 * Also, newer IBM firmware does not clear bat3 and 4 so
1107 * this makes sure it's done.
1108 *  -- Cort
1109 */
1110clear_bats:
1111	li	r10,0
1112
1113	mtspr	SPRN_DBAT0U,r10
1114	mtspr	SPRN_DBAT0L,r10
1115	mtspr	SPRN_DBAT1U,r10
1116	mtspr	SPRN_DBAT1L,r10
1117	mtspr	SPRN_DBAT2U,r10
1118	mtspr	SPRN_DBAT2L,r10
1119	mtspr	SPRN_DBAT3U,r10
1120	mtspr	SPRN_DBAT3L,r10
1121	mtspr	SPRN_IBAT0U,r10
1122	mtspr	SPRN_IBAT0L,r10
1123	mtspr	SPRN_IBAT1U,r10
1124	mtspr	SPRN_IBAT1L,r10
1125	mtspr	SPRN_IBAT2U,r10
1126	mtspr	SPRN_IBAT2L,r10
1127	mtspr	SPRN_IBAT3U,r10
1128	mtspr	SPRN_IBAT3L,r10
1129BEGIN_MMU_FTR_SECTION
1130	/* Here's a tweak: at this point, CPU setup have
1131	 * not been called yet, so HIGH_BAT_EN may not be
1132	 * set in HID0 for the 745x processors. However, it
1133	 * seems that doesn't affect our ability to actually
1134	 * write to these SPRs.
1135	 */
1136	mtspr	SPRN_DBAT4U,r10
1137	mtspr	SPRN_DBAT4L,r10
1138	mtspr	SPRN_DBAT5U,r10
1139	mtspr	SPRN_DBAT5L,r10
1140	mtspr	SPRN_DBAT6U,r10
1141	mtspr	SPRN_DBAT6L,r10
1142	mtspr	SPRN_DBAT7U,r10
1143	mtspr	SPRN_DBAT7L,r10
1144	mtspr	SPRN_IBAT4U,r10
1145	mtspr	SPRN_IBAT4L,r10
1146	mtspr	SPRN_IBAT5U,r10
1147	mtspr	SPRN_IBAT5L,r10
1148	mtspr	SPRN_IBAT6U,r10
1149	mtspr	SPRN_IBAT6L,r10
1150	mtspr	SPRN_IBAT7U,r10
1151	mtspr	SPRN_IBAT7L,r10
1152END_MMU_FTR_SECTION_IFSET(MMU_FTR_USE_HIGH_BATS)
1153	blr
1154
1155_ENTRY(update_bats)
1156	lis	r4, 1f@h
1157	ori	r4, r4, 1f@l
1158	tophys(r4, r4)
1159	mfmsr	r6
1160	mflr	r7
1161	li	r3, MSR_KERNEL & ~(MSR_IR | MSR_DR)
1162	rlwinm	r0, r6, 0, ~MSR_RI
1163	rlwinm	r0, r0, 0, ~MSR_EE
1164	mtmsr	r0
1165
1166	.align	4
1167	mtspr	SPRN_SRR0, r4
1168	mtspr	SPRN_SRR1, r3
1169	rfi
11701:	bl	clear_bats
1171	lis	r3, BATS@ha
1172	addi	r3, r3, BATS@l
1173	tophys(r3, r3)
1174	LOAD_BAT(0, r3, r4, r5)
1175	LOAD_BAT(1, r3, r4, r5)
1176	LOAD_BAT(2, r3, r4, r5)
1177	LOAD_BAT(3, r3, r4, r5)
1178BEGIN_MMU_FTR_SECTION
1179	LOAD_BAT(4, r3, r4, r5)
1180	LOAD_BAT(5, r3, r4, r5)
1181	LOAD_BAT(6, r3, r4, r5)
1182	LOAD_BAT(7, r3, r4, r5)
1183END_MMU_FTR_SECTION_IFSET(MMU_FTR_USE_HIGH_BATS)
1184	li	r3, MSR_KERNEL & ~(MSR_IR | MSR_DR | MSR_RI)
1185	mtmsr	r3
1186	mtspr	SPRN_SRR0, r7
1187	mtspr	SPRN_SRR1, r6
1188	rfi
1189
1190flush_tlbs:
1191	lis	r10, 0x40
11921:	addic.	r10, r10, -0x1000
1193	tlbie	r10
1194	bgt	1b
1195	sync
1196	blr
1197
1198mmu_off:
1199 	addi	r4, r3, __after_mmu_off - _start
1200	mfmsr	r3
1201	andi.	r0,r3,MSR_DR|MSR_IR		/* MMU enabled? */
1202	beqlr
1203	andc	r3,r3,r0
1204
1205	.align	4
1206	mtspr	SPRN_SRR0,r4
1207	mtspr	SPRN_SRR1,r3
1208	sync
1209	rfi
1210
1211/* We use one BAT to map up to 256M of RAM at _PAGE_OFFSET */
1212initial_bats:
1213	lis	r11,PAGE_OFFSET@h
1214	tophys(r8,r11)
1215#ifdef CONFIG_SMP
1216	ori	r8,r8,0x12		/* R/W access, M=1 */
1217#else
1218	ori	r8,r8,2			/* R/W access */
1219#endif /* CONFIG_SMP */
1220	ori	r11,r11,BL_256M<<2|0x2	/* set up BAT registers for 604 */
1221
1222	mtspr	SPRN_DBAT0L,r8		/* N.B. 6xx have valid */
1223	mtspr	SPRN_DBAT0U,r11		/* bit in upper BAT register */
1224	mtspr	SPRN_IBAT0L,r8
1225	mtspr	SPRN_IBAT0U,r11
1226	isync
1227	blr
1228
1229#ifdef CONFIG_BOOTX_TEXT
1230setup_disp_bat:
1231	/*
1232	 * setup the display bat prepared for us in prom.c
1233	 */
1234	mflr	r8
1235	bl	reloc_offset
1236	mtlr	r8
1237	addis	r8,r3,disp_BAT@ha
1238	addi	r8,r8,disp_BAT@l
1239	cmpwi	cr0,r8,0
1240	beqlr
1241	lwz	r11,0(r8)
1242	lwz	r8,4(r8)
1243	mtspr	SPRN_DBAT3L,r8
1244	mtspr	SPRN_DBAT3U,r11
1245	blr
1246#endif /* CONFIG_BOOTX_TEXT */
1247
1248#ifdef CONFIG_PPC_EARLY_DEBUG_CPM
1249setup_cpm_bat:
1250	lis	r8, 0xf000
1251	ori	r8, r8,	0x002a
1252	mtspr	SPRN_DBAT1L, r8
1253
1254	lis	r11, 0xf000
1255	ori	r11, r11, (BL_1M << 2) | 2
1256	mtspr	SPRN_DBAT1U, r11
1257
1258	blr
1259#endif
1260
1261#ifdef CONFIG_PPC_EARLY_DEBUG_USBGECKO
1262setup_usbgecko_bat:
1263	/* prepare a BAT for early io */
1264#if defined(CONFIG_GAMECUBE)
1265	lis	r8, 0x0c00
1266#elif defined(CONFIG_WII)
1267	lis	r8, 0x0d00
1268#else
1269#error Invalid platform for USB Gecko based early debugging.
1270#endif
1271	/*
1272	 * The virtual address used must match the virtual address
1273	 * associated to the fixmap entry FIX_EARLY_DEBUG_BASE.
1274	 */
1275	lis	r11, 0xfffe	/* top 128K */
1276	ori	r8, r8, 0x002a	/* uncached, guarded ,rw */
1277	ori	r11, r11, 0x2	/* 128K, Vs=1, Vp=0 */
1278	mtspr	SPRN_DBAT1L, r8
1279	mtspr	SPRN_DBAT1U, r11
1280	blr
1281#endif
1282
1283#ifdef CONFIG_8260
1284/* Jump into the system reset for the rom.
1285 * We first disable the MMU, and then jump to the ROM reset address.
1286 *
1287 * r3 is the board info structure, r4 is the location for starting.
1288 * I use this for building a small kernel that can load other kernels,
1289 * rather than trying to write or rely on a rom monitor that can tftp load.
1290 */
1291       .globl  m8260_gorom
1292m8260_gorom:
1293	mfmsr	r0
1294	rlwinm	r0,r0,0,17,15	/* clear MSR_EE in r0 */
1295	sync
1296	mtmsr	r0
1297	sync
1298	mfspr	r11, SPRN_HID0
1299	lis	r10, 0
1300	ori	r10,r10,HID0_ICE|HID0_DCE
1301	andc	r11, r11, r10
1302	mtspr	SPRN_HID0, r11
1303	isync
1304	li	r5, MSR_ME|MSR_RI
1305	lis	r6,2f@h
1306	addis	r6,r6,-KERNELBASE@h
1307	ori	r6,r6,2f@l
1308	mtspr	SPRN_SRR0,r6
1309	mtspr	SPRN_SRR1,r5
1310	isync
1311	sync
1312	rfi
13132:
1314	mtlr	r4
1315	blr
1316#endif
1317
1318
1319/*
1320 * We put a few things here that have to be page-aligned.
1321 * This stuff goes at the beginning of the data segment,
1322 * which is page-aligned.
1323 */
1324	.data
1325	.globl	sdata
1326sdata:
1327	.globl	empty_zero_page
1328empty_zero_page:
1329	.space	4096
1330EXPORT_SYMBOL(empty_zero_page)
1331
1332	.globl	swapper_pg_dir
1333swapper_pg_dir:
1334	.space	PGD_TABLE_SIZE
1335
1336/* Room for two PTE pointers, usually the kernel and current user pointers
1337 * to their respective root page table.
1338 */
1339abatron_pteptrs:
1340	.space	8
1341