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