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