cachepc-linux

Fork of AMDESE/linux with modifications for CachePC side-channel attack
git clone https://git.sinitax.com/sinitax/cachepc-linux
Log | Files | Refs | README | LICENSE | sfeed.txt

head_book3s_32.S (32652B)


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