xref: /freebsd/sys/powerpc/booke/locore.S (revision 33f12199250a09b573f7a518b523fdac3f120b8f)
1/*-
2 * Copyright (C) 2006 Semihalf, Marian Balakowicz <m8@semihalf.com>
3 * All rights reserved.
4 *
5 * Redistribution and use in source and binary forms, with or without
6 * modification, are permitted provided that the following conditions
7 * are met:
8 * 1. Redistributions of source code must retain the above copyright
9 *    notice, this list of conditions and the following disclaimer.
10 * 2. Redistributions in binary form must reproduce the above copyright
11 *    notice, this list of conditions and the following disclaimer in the
12 *    documentation and/or other materials provided with the distribution.
13 * 3. The name of the author may not be used to endorse or promote products
14 *    derived from this software without specific prior written permission.
15 *
16 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
17 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
18 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.  IN
19 * NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
20 * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED
21 * TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
22 * PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
23 * LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
24 * NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
25 * SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
26 *
27 * $FreeBSD$
28 */
29
30#include "assym.s"
31
32#include <machine/param.h>
33#include <machine/asm.h>
34#include <machine/spr.h>
35#include <machine/psl.h>
36#include <machine/pte.h>
37#include <machine/trap.h>
38#include <machine/vmparam.h>
39#include <machine/tlb.h>
40#include <machine/bootinfo.h>
41
42/*
43 * This symbol is here for the benefit of kvm_mkdb, and is supposed to
44 * mark the start of kernel text.
45 */
46	.text
47	.globl	kernel_text
48kernel_text:
49
50/*
51 * Startup entry.  Note, this must be the first thing in the text segment!
52 */
53	.text
54	.globl	__start
55__start:
56
57/*
58 * Assumption on a boot loader:
59 *  - system memory starts from physical address 0
60 *  - kernel is loaded at 16MB boundary
61 *  - it's mapped by a single TBL1 entry
62 *  - TLB1 mapping is 1:1 pa to va
63 *  - all PID registers are set to the same value
64 *
65 * Loader register use:
66 *	r1	: stack pointer
67 *	r3	: metadata pointer
68 *
69 * We rearrange the TLB1 layout as follows:
70 *  - find AS and entry kernel started in
71 *  - make sure it's protected, ivalidate other entries
72 *  - create temp entry in the second AS (make sure it's not TLB[15])
73 *  - switch to temp mapping
74 *  - map 16MB of RAM in TLB1[15]
75 *  - use AS=1, set EPN to KERNBASE and RPN to kernel load address
76 *  - switch to to TLB1[15] mapping
77 *  - invalidate temp mapping
78 *
79 * locore register use:
80 *	r1	: stack pointer
81 *	r2	: unused
82 *	r3	: kernel_text
83 *	r4	: _end
84 *	r5	: metadata pointer
85 *	r6-r9	: unused
86 *	r10	: entry we started in
87 *	r11	: temp entry
88 *	r12	: AS we started in
89 *	r13-r31 : auxiliary registers
90 */
91
92/*
93 * Move metadata ptr to r5
94 */
95	mr	%r5, %r3
96
97/*
98 * Initial cleanup
99 */
100	li	%r16, 0x200		/* Keep debug exceptions for CodeWarrior. */
101	mtmsr	%r16
102	isync
103#if 0
104	mtspr	SPR_HID0, %r16
105	isync
106	msync
107	mtspr	SPR_HID1, %r16
108	isync
109#endif
110
111	/* Issue INV_ALL Invalidate on TLB0 */
112	li      %r16, 0x04
113	tlbivax	0, %r16
114	isync
115	msync
116
117/*
118 * Use tblsx to locate the TLB1 entry that maps kernel code
119 */
120	bl	1f			/* Current address */
1211:	mflr	%r15
122
123	/* Find entry that maps current address */
124	mfspr	%r17, SPR_PID0
125	slwi	%r17, %r17, MAS6_SPID0_SHIFT
126	mtspr	SPR_MAS6, %r17
127	isync
128	tlbsx	0, %r15
129
130	/* Copy entry number to r10 */
131	mfspr	%r17, SPR_MAS0
132	rlwinm	%r10, %r17, 16, 28, 31
133
134	/* Invalidate TLB1, skipping our entry. */
135	mfspr	%r17, SPR_TLB1CFG	/* Get number of entries */
136	andi.	%r17, %r17, TLBCFG_NENTRY_MASK@l
137	li	%r16, 0			/* Start from Entry 0 */
138
1392:	lis	%r15, MAS0_TLBSEL1@h	/* Select TLB1 */
140	rlwimi	%r15, %r16, 16, 12, 15
141	mtspr	SPR_MAS0, %r15
142	isync
143	tlbre
144	mfspr	%r15, SPR_MAS1
145	cmpw	%r16, %r10
146	beq	3f
147	/* Clear VALID and IPROT bits for other entries */
148	rlwinm	%r15, %r15, 0, 2, 31
149	mtspr	SPR_MAS1, %r15
150	isync
151	tlbwe
152	isync
153	msync
1543:	addi	%r16, %r16, 1
155	cmpw	%r16, %r17		/* Check if this is the last entry */
156	bne	2b
157
158/*
159 * Create temporary mapping in the other Address Space
160 */
161	lis	%r17, MAS0_TLBSEL1@h	/* Select TLB1 */
162	rlwimi	%r17, %r10, 16, 12, 15	/* Select our entry */
163	mtspr	SPR_MAS0, %r17
164	isync
165	tlbre				/* Read it in */
166
167	/* Prepare and write temp entry */
168	lis	%r17, MAS0_TLBSEL1@h	/* Select TLB1 */
169	addi	%r11, %r10, 0x1		/* Use next entry. */
170	rlwimi	%r17, %r11, 16, 12, 15	/* Select temp entry */
171	mtspr	SPR_MAS0, %r17
172	isync
173
174	mfspr	%r16, SPR_MAS1
175	li	%r15, 1			/* AS 1 */
176	rlwimi	%r16, %r15, 12, 19, 19
177	mtspr	SPR_MAS1, %r16
178	li	%r17, 0
179	rlwimi	%r16, %r17, 0, 8, 15	/* Global mapping, TID=0 */
180	isync
181
182	tlbwe
183	isync
184	msync
185
186	mfmsr	%r16
187	ori	%r16, %r16, 0x30	/* Switch to AS 1. */
188
189	bl	4f			/* Find current execution address */
1904:	mflr	%r15
191	addi	%r15, %r15, 20		/* Increment to instruction after rfi */
192	mtspr	SPR_SRR0, %r15
193	mtspr	SPR_SRR1, %r16
194	rfi				/* Switch context */
195
196/*
197 * Invalidate initial entry
198 */
199	mr	%r22, %r10
200	bl	tlb1_inval_entry
201
202/*
203 * Setup final mapping in TLB1[1] and switch to it
204 */
205	/* Final kernel mapping, map in 16 MB of RAM */
206	lis	%r16, MAS0_TLBSEL1@h	/* Select TLB1 */
207	li	%r17, 1			/* Entry 1 */
208	rlwimi	%r16, %r17, 16, 12, 15
209	mtspr	SPR_MAS0, %r16
210	isync
211
212	li	%r16, (TLB_SIZE_16M << MAS1_TSIZE_SHIFT)@l
213	oris	%r16, %r16, (MAS1_VALID | MAS1_IPROT)@h
214	mtspr	SPR_MAS1, %r16
215	isync
216
217	lis	%r19, KERNBASE@h
218	ori	%r19, %r19, KERNBASE@l
219	mtspr	SPR_MAS2, %r19		/* Set final EPN, clear WIMG */
220	isync
221
222	bl	5f
2235:	mflr	%r16			/* Use current address */
224	lis	%r18, 0xff00		/* 16MB alignment mask */
225	and	%r16, %r16, %r18
226	mr	%r25, %r16		/* Copy kernel load address */
227	ori	%r16, %r16, (MAS3_SX | MAS3_SW | MAS3_SR)@l
228	mtspr	SPR_MAS3, %r16		/* Set RPN and protection */
229	isync
230	tlbwe
231	isync
232	msync
233
234	/* Switch to the above TLB1[1] mapping */
235	lis	%r18, 0x00ff		/* 16MB offset mask */
236	ori	%r18, %r18, 0xffff
237	bl	6f
2386:	mflr	%r20			/* Use current address */
239	and	%r20, %r20, %r18	/* Offset from kernel load address */
240	add	%r20, %r20, %r19	/* Move to kernel virtual address */
241	addi	%r20, %r20, 32		/* Increment to instr. after rfi  */
242	li	%r21, 0x200
243	mtspr   SPR_SRR0, %r20
244	mtspr   SPR_SRR1, %r21
245	rfi
246
247	/* Save kernel load address for later use */
248	lis	%r24, kernload@ha
249	addi	%r24, %r24, kernload@l
250	stw	%r25, 0(%r24)
251
252/*
253 * Invalidate temp mapping
254 */
255	mr	%r22, %r11
256	bl	tlb1_inval_entry
257
258/*
259 * Setup a temporary stack
260 */
261	lis	%r1, kstack0_space@ha
262	addi	%r1, %r1, kstack0_space@l
263	addi	%r1, %r1, (16384 - 512)
264
265/*
266 * Intialise exception vector offsets
267 */
268	bl	ivor_setup
269
270/*
271 * Jump to system initialization code
272 *
273 * Setup first two arguments for e500_init, metadata (r5) is already in place.
274 */
275	lis	%r3, kernel_text@ha
276	addi	%r3, %r3, kernel_text@l
277	lis	%r4, _end@ha
278	addi	%r4, %r4, _end@l
279
280	bl	e500_init   /* Prepare e500 core */
281	bl	mi_startup  /* Machine independet part, does not return */
282
283/************************************************************************/
284/* locore subroutines */
285/************************************************************************/
286
287tlb1_inval_entry:
288	lis	%r17, MAS0_TLBSEL1@h	/* Select TLB1 */
289	rlwimi	%r17, %r22, 16, 12, 15	/* Select our entry */
290	mtspr	SPR_MAS0, %r17
291	isync
292	tlbre				/* Read it in */
293
294	li	%r16, 0
295	mtspr	SPR_MAS1, %r16
296	isync
297	tlbwe
298	isync
299	msync
300	blr
301
302ivor_setup:
303	/* Set base address of interrupt handler routines */
304	lis	%r21, interrupt_vector_base@h
305	mtspr	SPR_IVPR, %r21
306
307	/* Assign interrupt handler routines offsets */
308	li	%r21, int_critical_input@l
309	mtspr	SPR_IVOR0, %r21
310	li	%r21, int_machine_check@l
311	mtspr	SPR_IVOR1, %r21
312	li	%r21, int_data_storage@l
313	mtspr	SPR_IVOR2, %r21
314	li	%r21, int_instr_storage@l
315	mtspr	SPR_IVOR3, %r21
316	li	%r21, int_external_input@l
317	mtspr	SPR_IVOR4, %r21
318	li	%r21, int_alignment@l
319	mtspr	SPR_IVOR5, %r21
320	li	%r21, int_program@l
321	mtspr	SPR_IVOR6, %r21
322	li	%r21, int_syscall@l
323	mtspr	SPR_IVOR8, %r21
324	li	%r21, int_decrementer@l
325	mtspr	SPR_IVOR10, %r21
326	li	%r21, int_fixed_interval_timer@l
327	mtspr	SPR_IVOR11, %r21
328	li	%r21, int_watchdog@l
329	mtspr	SPR_IVOR12, %r21
330	li	%r21, int_data_tlb_error@l
331	mtspr	SPR_IVOR13, %r21
332	li	%r21, int_inst_tlb_error@l
333	mtspr	SPR_IVOR14, %r21
334	li	%r21, int_debug@l
335	mtspr	SPR_IVOR15, %r21
336	blr
337
338/*
339 * void tlb1_inval_va(vm_offset_t va)
340 *
341 * r3 - va to invalidate
342 */
343ENTRY(tlb1_inval_va)
344	/* EA mask */
345	lis	%r6, 0xffff
346	ori	%r6, %r6, 0xf000
347	and	%r3, %r3, %r6
348
349	/* Select TLB1 */
350	ori	%r3, %r3, 0x08
351
352	isync
353	tlbivax 0, %r3
354	isync
355	msync
356	blr
357
358/*
359 * void tlb0_inval_va(vm_offset_t va)
360 *
361 * r3 - va to invalidate
362 */
363ENTRY(tlb0_inval_va)
364	/* EA mask, this also clears TLBSEL, selecting TLB0 */
365	lis	%r6, 0xffff
366	ori	%r6, %r6, 0xf000
367	and	%r3, %r3, %r6
368
369	isync
370	tlbivax 0, %r3
371	isync
372	msync
373	blr
374
375/*
376 * Cache disable/enable/inval sequences according
377 * to section 2.16 of E500CORE RM.
378 */
379ENTRY(dcache_inval)
380	/* Invalidate d-cache */
381	mfspr	%r3, SPR_L1CSR0
382	ori	%r3, %r3, (L1CSR0_DCFI | L1CSR0_DCLFR)@l
383	msync
384	isync
385	mtspr	SPR_L1CSR0, %r3
386	isync
387	blr
388
389ENTRY(dcache_disable)
390	/* Disable d-cache */
391	mfspr	%r3, SPR_L1CSR0
392	li	%r4, L1CSR0_DCE@l
393	not	%r4, %r4
394	and	%r3, %r3, %r4
395	msync
396	isync
397	mtspr	SPR_L1CSR0, %r3
398	isync
399	blr
400
401ENTRY(dcache_enable)
402	/* Enable d-cache */
403	mfspr	%r3, SPR_L1CSR0
404	oris	%r3, %r3, (L1CSR0_DCPE | L1CSR0_DCE)@h
405	ori	%r3, %r3, (L1CSR0_DCPE | L1CSR0_DCE)@l
406	msync
407	isync
408	mtspr	SPR_L1CSR0, %r3
409	isync
410	blr
411
412ENTRY(icache_inval)
413	/* Invalidate i-cache */
414	mfspr	%r3, SPR_L1CSR1
415	ori	%r3, %r3, (L1CSR1_ICFI | L1CSR1_ICLFR)@l
416	isync
417	mtspr	SPR_L1CSR1, %r3
418	isync
419	blr
420
421ENTRY(icache_disable)
422	/* Disable i-cache */
423	mfspr	%r3, SPR_L1CSR1
424	li	%r4, L1CSR1_ICE@l
425	not	%r4, %r4
426	and	%r3, %r3, %r4
427	isync
428	mtspr	SPR_L1CSR1, %r3
429	isync
430	blr
431
432ENTRY(icache_enable)
433	/* Enable i-cache */
434	mfspr	%r3, SPR_L1CSR1
435	oris	%r3, %r3, (L1CSR1_ICPE | L1CSR1_ICE)@h
436	ori	%r3, %r3, (L1CSR1_ICPE | L1CSR1_ICE)@l
437	isync
438	mtspr	SPR_L1CSR1, %r3
439	isync
440	blr
441
442/*
443 * int setfault()
444 *
445 * Similar to setjmp to setup for handling faults on accesses to user memory.
446 * Any routine using this may only call bcopy, either the form below,
447 * or the (currently used) C code optimized, so it doesn't use any non-volatile
448 * registers.
449 */
450	.globl	setfault
451setfault:
452	mflr	%r0
453	mfsprg0	%r4
454	lwz	%r4, PC_CURTHREAD(%r4)
455	lwz	%r4, TD_PCB(%r4)
456	stw	%r3, PCB_ONFAULT(%r4)
457	mfcr	%r10
458	mfctr	%r11
459	mfxer	%r12
460	stw	%r0, 0(%r3)
461	stw	%r1, 4(%r3)
462	stw	%r2, 8(%r3)
463	stmw	%r10, 12(%r3)		/* store CR, CTR, XER, [r13 .. r31] */
464	li	%r3, 0			/* return FALSE */
465	blr
466
467/************************************************************************/
468/* Data section								*/
469/************************************************************************/
470	.data
471	.align	4
472GLOBAL(kstack0_space)
473	.space	16384
474
475/*
476 * Compiled KERNBASE locations
477 */
478	.globl	kernbase
479	.set	kernbase, KERNBASE
480
481/*
482 * Globals
483 */
484#define	INTSTK		16384		/* 16K interrupt stack */
485#define	INTRCNT_COUNT	256		/* max(HROWPIC_IRQMAX,OPENPIC_IRQMAX) */
486
487GLOBAL(kernload)
488	.long
489GLOBAL(intrnames)
490	.space	INTRCNT_COUNT * (MAXCOMLEN + 1) * 2
491GLOBAL(eintrnames)
492	.align 4
493GLOBAL(intrcnt)
494	.space	INTRCNT_COUNT * 4 * 2
495GLOBAL(eintrcnt)
496
497#include <powerpc/booke/trap_subr.S>
498