xref: /freebsd/sys/arm64/arm64/locore.S (revision f38792ffc2db67ca82026eb4861f37fe7ac7c38e)
1/*-
2 * Copyright (c) 2012-2014 Andrew Turner
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 *
14 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
15 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
16 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
17 * ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
18 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
19 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
20 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
21 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
22 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
23 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
24 * SUCH DAMAGE.
25 */
26
27#include "assym.inc"
28#include "opt_kstack_pages.h"
29#include <sys/elf_common.h>
30#include <sys/syscall.h>
31#include <machine/asm.h>
32#include <machine/armreg.h>
33#include <machine/cpu.h>
34#include <machine/hypervisor.h>
35#include <machine/param.h>
36#include <machine/pte.h>
37#include <machine/vm.h>
38#include <machine/vmparam.h>
39
40#define	VIRT_BITS	48
41
42/*
43 * Loads a 64-bit value into reg using 1 to 4 mov/movk instructions.
44 * This can be used early on when we don't know the CPUs endianness.
45 */
46.macro	mov_q reg, val
47	mov	\reg, :abs_g0_nc:\val
48.if (\val >> 16) & 0xffff != 0
49	movk	\reg, :abs_g1_nc:\val
50.endif
51.if (\val >> 32) & 0xffff != 0
52	movk	\reg, :abs_g2_nc:\val
53.endif
54.if (\val >> 48) & 0xffff != 0
55	movk	\reg, :abs_g3:\val
56.endif
57.endm
58
59#if PAGE_SIZE == PAGE_SIZE_16K
60/*
61 * The number of level 3 tables to create. 32 will allow for 1G of address
62 * space, the same as a single level 2 page with 4k pages.
63 */
64#define	L3_PAGE_COUNT	32
65#elif PAGE_SIZE == PAGE_SIZE_4K
66/*
67 * Space for a level 3 table holding the end of the executable memory and
68 * the start of the non-executable data.
69 */
70#define	L3_PAGE_COUNT	1
71#endif
72
73/*
74 * The size of our bootstrap stack.
75 */
76#define	BOOT_STACK_SIZE	(KSTACK_PAGES * PAGE_SIZE)
77
78	.globl	kernbase
79	.set	kernbase, KERNBASE
80
81/*
82 * We assume:
83 *  MMU      on with an identity map, or off
84 *  D-Cache: off
85 *  I-Cache: on or off
86 *  We are loaded at a 2MiB aligned address
87 */
88
89ENTRY(_start)
90	/* Enter the kernel exception level */
91	bl	enter_kernel_el
92
93	/* Set the context id */
94	msr	contextidr_el1, xzr
95
96	/* Get the virt -> phys offset */
97	bl	get_load_phys_addr
98
99	/*
100	 * At this point:
101	 * x28 = Our physical load address
102	 */
103
104	/* Create the page tables */
105	bl	create_pagetables
106
107	/*
108	 * At this point:
109	 * x27 = TTBR0 table
110	 * x24 = TTBR1 table
111	 * x22 = PTE shareability attributes
112	 * x21 = BTI guarded page attribute if supported
113	 */
114
115	/* Enable the mmu */
116	bl	start_mmu
117
118	/* Load the new ttbr0 pagetable */
119	adrp	x27, pagetable_l0_ttbr0
120	add	x27, x27, :lo12:pagetable_l0_ttbr0
121
122	/* Jump to the virtual address space */
123	ldr	x15, .Lvirtdone
124	br	x15
125
126virtdone:
127	BTI_J
128
129	/* Set up the stack */
130	adrp	x25, initstack_end
131	add	x25, x25, :lo12:initstack_end
132	sub	sp, x25, #PCB_SIZE
133
134	/* Zero the BSS */
135	ldr	x15, .Lbss
136	ldr	x14, .Lend
1371:
138	stp	xzr, xzr, [x15], #16
139	cmp	x15, x14
140	b.lo	1b
141
142#if defined(PERTHREAD_SSP)
143	/* Set sp_el0 to the boot canary for early per-thread SSP to work */
144	adrp	x15, boot_canary
145	add	x15, x15, :lo12:boot_canary
146	msr	sp_el0, x15
147#endif
148
149	/* Backup the module pointer */
150	mov	x1, x0
151
152	sub	sp, sp, #BOOTPARAMS_SIZE
153	mov	x0, sp
154
155	str	x1,  [x0, #BP_MODULEP]
156	adrp	x25, initstack
157	add	x25, x25, :lo12:initstack
158	str	x25, [x0, #BP_KERN_STACK]
159	str	x27, [x0, #BP_KERN_TTBR0]
160	str	x23, [x0, #BP_BOOT_EL]
161
162	/* Set these before they are used in kasan_init_early */
163	adrp	x1, pmap_sh_attr
164	str	x22, [x1, :lo12:pmap_sh_attr]
165#ifdef __ARM_FEATURE_BTI_DEFAULT
166	adrp	x1, pmap_gp_attr
167	str	x21, [x1, :lo12:pmap_gp_attr]
168#endif
169
170#ifdef KASAN
171	/* Save bootparams */
172	mov	x19, x0
173
174	/* Bootstrap an early shadow map for the boot stack. */
175	ldr	x0, [x0, #BP_KERN_STACK]
176	ldr	x1, =BOOT_STACK_SIZE
177	bl	kasan_init_early
178
179	/* Restore bootparams */
180	mov	x0, x19
181#endif
182
183	/* trace back starts here */
184	mov	fp, #0
185	/* Branch to C code */
186	bl	initarm
187	/* We are done with the boot params */
188	add	sp, sp, #BOOTPARAMS_SIZE
189
190	/*
191	 * Enable pointer authentication in the kernel. We set the keys for
192	 * thread0 in initarm so have to wait until it returns to enable it.
193	 * If we were to enable it in initarm then any authentication when
194	 * returning would fail as it was called with pointer authentication
195	 * disabled.
196	 */
197	bl	ptrauth_start
198
199	bl	mi_startup
200
201	/* We should not get here */
202	brk	0
203
204	.align 3
205.Lvirtdone:
206	.quad	virtdone
207.Lbss:
208	.quad	__bss_start
209.Lend:
210	.quad	__bss_end
211END(_start)
212
213#ifdef SMP
214/*
215 * void
216 * mpentry_psci(unsigned long)
217 *
218 * Called by a core when it is being brought online with psci.
219 * The data in x0 is passed straight to init_secondary.
220 */
221ENTRY(mpentry_psci)
222	mov	x26, xzr
223	b	mpentry_common
224END(mpentry_psci)
225
226/*
227 * void
228 * mpentry_spintable(void)
229 *
230 * Called by a core when it is being brought online with a spin-table.
231 * Reads the new CPU ID and passes this to init_secondary.
232 */
233ENTRY(mpentry_spintable)
234	ldr	x26, =spintable_wait
235	b	mpentry_common
236END(mpentry_spintable)
237
238/* Wait for the current CPU to be released */
239LENTRY(spintable_wait)
240	/* Read the affinity bits from mpidr_el1 */
241	mrs	x1, mpidr_el1
242	ldr	x2, =CPU_AFF_MASK
243	and	x1, x1, x2
244
245	adrp	x2, ap_cpuid
2461:
247	ldr	x0, [x2, :lo12:ap_cpuid]
248	cmp	x0, x1
249	b.ne	1b
250
251	str	xzr, [x2, :lo12:ap_cpuid]
252	dsb	sy
253	sev
254
255	ret
256LEND(mpentry_spintable)
257
258LENTRY(mpentry_common)
259	/* Disable interrupts */
260	msr	daifset, #DAIF_INTR
261
262	/* Enter the kernel exception level */
263	bl	enter_kernel_el
264
265	/* Set the context id */
266	msr	contextidr_el1, xzr
267
268	/* Load the kernel page table */
269	adrp	x24, pagetable_l0_ttbr1
270	add	x24, x24, :lo12:pagetable_l0_ttbr1
271	/* Load the identity page table */
272	adrp	x27, pagetable_l0_ttbr0_bootstrap
273	add	x27, x27, :lo12:pagetable_l0_ttbr0_bootstrap
274
275	/* Enable the mmu */
276	bl	start_mmu
277
278	/* Load the new ttbr0 pagetable */
279	adrp	x27, pagetable_l0_ttbr0
280	add	x27, x27, :lo12:pagetable_l0_ttbr0
281
282	/* Jump to the virtual address space */
283	ldr	x15, =mp_virtdone
284	br	x15
285
286mp_virtdone:
287	BTI_J
288
289	/*
290	 * Allow this CPU to wait until the kernel is ready for it,
291	 * e.g. with spin-table but each CPU uses the same release address
292	 */
293	cbz	x26, 1f
294	blr	x26
2951:
296
297	/* Start using the AP boot stack */
298	adrp	x4, bootstack
299	ldr	x4, [x4, :lo12:bootstack]
300	mov	sp, x4
301
302#if defined(PERTHREAD_SSP)
303	/* Set sp_el0 to the boot canary for early per-thread SSP to work */
304	adrp	x15, boot_canary
305	add	x15, x15, :lo12:boot_canary
306	msr	sp_el0, x15
307#endif
308
309	/* Load the kernel ttbr0 pagetable */
310	msr	ttbr0_el1, x27
311	isb
312
313	/* Invalidate the TLB */
314	tlbi	vmalle1
315	dsb	sy
316	isb
317
318	/*
319	 * Initialize the per-CPU pointer before calling into C code, for the
320	 * benefit of kernel sanitizers.
321	 */
322	adrp	x18, bootpcpu
323	ldr	x18, [x18, :lo12:bootpcpu]
324	msr	tpidr_el1, x18
325
326	b	init_secondary
327LEND(mpentry_common)
328#endif
329
330/*
331 * Enter the exception level the kernel will use:
332 *
333 *  - If in EL1 continue in EL1
334 *  - If the CPU supports FEAT_VHE then set HCR_E2H and HCR_TGE and continue
335 *    in EL2
336 *  - Configure EL2 to support running the kernel at EL1 and exit to that
337 */
338LENTRY(enter_kernel_el)
339	mrs	x23, CurrentEL
340	and	x23, x23, #(CURRENTEL_EL_MASK)
341	cmp	x23, #(CURRENTEL_EL_EL2)
342	b.eq	1f
343
344	/*
345	 * Ensure there are no memory operations here. If the boot loader
346	 * enters the kernel in big-endian mode then loading sctlr will
347	 * be incorrect. As instructions are the same in both endians it is
348	 * safe to use mov instructions.
349	 */
350	mov_q	x2, SCTLR_MMU_OFF
351	msr	sctlr_el1, x2
352	/*
353	 * SCTLR_EOS is set to make eret a context synchronizing event. We
354	 * need an isb here to ensure it's observed by later instructions,
355	 * but don't need it in the eret below.
356	 */
357	isb
358
359	/*
360	 * Ensure SPSR_EL1 and pstate are in sync. The only way to set the
361	 * latter is to set the former and return from an exception with eret.
362	 */
363	mov	x2, #(PSR_DAIF | PSR_M_EL1h)
364	msr	spsr_el1, x2
365	msr	elr_el1, lr
366	eret
367
3681:
369	dsb	sy
370	/*
371	 * Set just the reserved bits in sctlr_el2. This will disable the
372	 * MMU which may have broken the kernel if we enter the kernel in
373	 * EL2, e.g. when using VHE.
374	 *
375	 * As with sctlr_el1 above use mov instructions to ensure there are
376	 * no memory operations.
377	 */
378	mov_q	x2, (SCTLR_EL2_RES1 | SCTLR_EL2_EIS | SCTLR_EL2_EOS)
379	msr	sctlr_el2, x2
380	isb
381
382	/*
383	 * The hardware is now in little-endian mode so memory operations
384	 * are safe.
385	 */
386
387	/* Configure the Hypervisor */
388	ldr	x2, =(HCR_RW | HCR_APK | HCR_API)
389	msr	hcr_el2, x2
390
391	/* Stash value of HCR_EL2 for later */
392	isb
393	mrs	x4, hcr_el2
394
395	/* Load the Virtualization Process ID Register */
396	mrs	x2, midr_el1
397	msr	vpidr_el2, x2
398
399	/* Load the Virtualization Multiprocess ID Register */
400	mrs	x2, mpidr_el1
401	msr	vmpidr_el2, x2
402
403	/* Set the initial sctlr_el1 */
404	ldr	x2, =SCTLR_MMU_OFF
405	msr	sctlr_el1, x2
406
407	/* Check for VHE */
408	CHECK_CPU_FEAT(x2, ID_AA64MMFR1, VH, IMPL, .Lno_vhe)
409
410	/*
411	 * The kernel will be running in EL2, route exceptions here rather
412	 * than EL1.
413	 */
414	orr	x4, x4, #HCR_E2H
415	orr	x4, x4, #HCR_TGE
416	msr	hcr_el2, x4
417	isb
418
419	msr	SCTLR_EL12_REG, x2
420	mov	x2, xzr /* CPTR_EL2 is managed by vfp.c */
421	ldr	x3, =(CNTHCTL_E2H_EL1PCTEN_NOTRAP | CNTHCTL_E2H_EL1PTEN_NOTRAP)
422	ldr	x5, =(PSR_DAIF | PSR_M_EL2h)
423	b	.Ldone_vhe
424
425.Lno_vhe:
426	/* Hypervisor trap functions */
427	adrp	x2, hyp_stub_vectors
428	add	x2, x2, :lo12:hyp_stub_vectors
429	msr	vbar_el2, x2
430
431	ldr	x2, =(CPTR_RES1)
432	ldr	x3, =(CNTHCTL_EL1PCTEN_NOTRAP | CNTHCTL_EL1PCEN_NOTRAP)
433	ldr	x5, =(PSR_DAIF | PSR_M_EL1h)
434
435.Ldone_vhe:
436
437	msr	cptr_el2, x2
438	/* Enable access to the physical timers at EL1 */
439	msr	cnthctl_el2, x3
440	/* Set the return PSTATE */
441	msr	spsr_el2, x5
442
443	/*
444	 * Configure the Extended Hypervisor register. This is only valid if
445	 * FEAT_HCX is enabled.
446	 */
447	CHECK_CPU_FEAT(x2, ID_AA64MMFR1, HCX, IMPL, 2f)
448	/* Extended Hypervisor Configuration */
449	msr	HCRX_EL2_REG, xzr
450	isb
4512:
452
453	/* Don't trap to EL2 for CP15 traps */
454	msr	hstr_el2, xzr
455
456	/* Set the counter offset to a known value */
457	msr	cntvoff_el2, xzr
458
459	/* Zero vttbr_el2 so a hypervisor can tell the host and guest apart */
460	msr	vttbr_el2, xzr
461
462	/* Check the CPU supports GIC, and configure the CPU interface */
463	CHECK_CPU_FEAT(x2, ID_AA64PFR0, GIC, CPUIF_EN, 3f)
464
465	mrs	x2, icc_sre_el2
466	orr	x2, x2, #ICC_SRE_EL2_EN	/* Enable access from insecure EL1 */
467	orr	x2, x2, #ICC_SRE_EL2_SRE	/* Enable system registers */
468	msr	icc_sre_el2, x2
4693:
470
471	/* Set the address to return to our return address */
472	msr	elr_el2, x30
473	isb
474
475	eret
476LEND(enter_kernel_el)
477
478/*
479 * Get the physical address the kernel was loaded at.
480 */
481LENTRY(get_load_phys_addr)
482	/* Load the offset of get_load_phys_addr from KERNBASE */
483	ldr	x28, =(get_load_phys_addr - KERNBASE)
484	/* Load the physical address of get_load_phys_addr */
485	adr	x29, get_load_phys_addr
486	/* Find the physical address of KERNBASE, i.e. our load address */
487	sub	x28, x29, x28
488	ret
489LEND(get_load_phys_addr)
490
491/*
492 * This builds the page tables containing the identity map, and the kernel
493 * virtual map.
494 *
495 * It relys on:
496 *  We were loaded to an address that is on a 2MiB boundary
497 *  All the memory must not cross a 1GiB boundaty
498 *  x28 contains the physical address we were loaded from
499 *
500 *  There are 7 or 8 pages before that address for the page tables
501 *   The pages used are:
502 *    - The Kernel L3 tables (only for 16k kernel)
503 *    - The Kernel L2 table
504 *    - The Kernel L1 table
505 *    - The Kernel L0 table             (TTBR1)
506 *    - The identity (PA = VA) L2 table
507 *    - The identity (PA = VA) L1 table
508 *    - The identity (PA = VA) L0 table (Early TTBR0)
509 *    - The Kernel empty L0 table       (Late TTBR0)
510 */
511LENTRY(create_pagetables)
512	/* Save the Link register */
513	mov	x5, x30
514
515	/* Clean the page table */
516	adrp	x6, pagetable
517	add	x6, x6, :lo12:pagetable
518	adrp	x27, pagetable_end
519	add	x27, x27, :lo12:pagetable_end
5201:
521	stp	xzr, xzr, [x6], #16
522	stp	xzr, xzr, [x6], #16
523	stp	xzr, xzr, [x6], #16
524	stp	xzr, xzr, [x6], #16
525	cmp	x6, x27
526	b.lo	1b
527
528#ifdef __ARM_FEATURE_BTI_DEFAULT
529	/*
530	 * Check if the CPU supports BTI
531	 */
532	mrs	x6, id_aa64pfr1_el1		/* Read the ID register */
533	and	x6, x6, ID_AA64PFR1_BT_MASK	/* Mask the field we need */
534	cmp	x6, xzr				/* Check it's non-zero */
535	cset	x6, ne				/* x6 is set if non-zero */
536	lsl	x21, x6, ATTR_S1_GP_SHIFT	/* Shift to the correct bit */
537#endif
538
539	/*
540	 * Find the shareability attribute we should use. If FEAT_LPA2 is
541	 * enabled then the shareability field is moved from the page table
542	 * to tcr_el1 and the bits in the page table are reused by the
543	 * address field.
544	 */
545#if PAGE_SIZE == PAGE_SIZE_4K
546#define	LPA2_MASK	ID_AA64MMFR0_TGran4_MASK
547#define	LPA2_VAL	ID_AA64MMFR0_TGran4_LPA2
548#elif PAGE_SIZE == PAGE_SIZE_16K
549#define	LPA2_MASK	ID_AA64MMFR0_TGran16_MASK
550#define	LPA2_VAL	ID_AA64MMFR0_TGran16_LPA2
551#else
552#error Unsupported page size
553#endif
554	mrs	x6, id_aa64mmfr0_el1
555	mov	x7, LPA2_VAL
556	and	x6, x6, LPA2_MASK
557	cmp	x6, x7
558	ldr	x22, =(ATTR_SH(ATTR_SH_IS))
559	csel	x22, xzr, x22, eq
560#undef LPA2_MASK
561#undef LPA2_VAL
562
563	/*
564	 * Build the TTBR1 maps.
565	 */
566
567	/* Find the size of the kernel */
568	mov	x6, #(KERNBASE)
569
570#if defined(LINUX_BOOT_ABI)
571	/* X19 is used as 'map FDT data' flag */
572	mov	x19, xzr
573
574	/* No modules or FDT pointer ? */
575	cbz	x0, booti_no_fdt
576
577	/*
578	 * Test if x0 points to modules descriptor(virtual address) or
579	 * to FDT (physical address)
580	 */
581	cmp	x0, x6		/* x6 is #(KERNBASE) */
582	b.lo	booti_fdt
583#endif
584
585	/* Booted with modules pointer */
586	/* Find modulep - begin */
587	sub	x8, x0, x6
588	/*
589	 * Add space for the module data. When PAGE_SIZE is 4k this will
590	 * add at least 2 level 2 blocks (2 * 2MiB). When PAGE_SIZE is
591	 * larger it will be at least as large as we use smaller level 3
592	 * pages.
593	 */
594	ldr	x7, =((6 * 1024 * 1024) - 1)
595	add	x8, x8, x7
596	b	common
597
598#if defined(LINUX_BOOT_ABI)
599booti_fdt:
600	/* Booted by U-Boot booti with FDT data */
601	/* Set 'map FDT data' flag */
602	mov	x19, #1
603
604booti_no_fdt:
605	/* Booted by U-Boot booti without FTD data */
606	/* Find the end - begin */
607	ldr     x7, .Lend
608	sub     x8, x7, x6
609
610	/*
611	 * Add one 2MiB page for copy of FDT data (maximum FDT size),
612	 * one for metadata and round up
613	 */
614	ldr	x7, =(3 * L2_SIZE - 1)
615	add	x8, x8, x7
616#endif
617
618common:
619#if PAGE_SIZE != PAGE_SIZE_4K
620	/*
621	 * Create L3 and L3C pages. The kernel will be loaded at a 2M aligned
622	 * address, enabling the creation of L3C pages. However, when the page
623	 * size is larger than 4k, L2 blocks are too large to map the kernel
624	 * with 2M alignment.
625	 */
626#define	PTE_SHIFT	L3_SHIFT
627#define	LL_PAGE_TABLE	pagetable_l3_ttbr1
628#define	BUILD_PTE_FUNC	build_l3_page_pagetable
629#else
630#define	PTE_SHIFT	L2_SHIFT
631#define	LL_PAGE_TABLE	pagetable_l2_ttbr1
632#define	BUILD_PTE_FUNC	build_l2_block_pagetable
633#endif
634
635	/* Get the number of blocks/pages to allocate, rounded down */
636	lsr	x14, x8, #(PTE_SHIFT)
637
638	ldr	x26, =etext
639#if PAGE_SIZE != PAGE_SIZE_4K
640	ldr	x8, =((1 << PTE_SHIFT) - 1)
641	add	x26, x26, x8
642#endif
643	mov	x8, #(KERNBASE)
644	sub	x25, x26, x8
645	lsr	x25, x25, #(PTE_SHIFT)
646
647#if PAGE_SIZE == PAGE_SIZE_4K
648	/* Calculate the number of executable level 3 pages to create */
649	lsr	x26, x26, #(L3_SHIFT)
650	bfc	x26, #(Ln_ENTRIES_SHIFT), #(64 - Ln_ENTRIES_SHIFT)
651
652	/* Build the L3 table holding the end of the exectuable code */
653	lsl	x15, x25, #(PTE_SHIFT)
654	adrp	x6, pagetable_l3_ttbr1
655	add	x6, x6, :lo12:pagetable_l3_ttbr1
656	ldr	x7, =(ATTR_S1_IDX(VM_MEMATTR_WRITE_BACK) | \
657	    ATTR_S1_AP(ATTR_S1_AP_RO))
658	ldr	x8, =(KERNBASE)
659	add	x8, x8, x15
660	add	x9, x28, x15
661	mov	x10, x26
662	bl	build_l3_page_pagetable
663
664	/* Build the remaining level 3 pages */
665	ldr	x7, =(ATTR_S1_IDX(VM_MEMATTR_WRITE_BACK) | ATTR_S1_XN)
666	lsl	x27, x26, #(L3_SHIFT)
667	add	x8, x8, x27
668	add	x9, x28, x15
669	add	x9, x9, x27
670	ldr	x10, =(Ln_ENTRIES)
671	sub	x10, x10, x26
672	bl	build_l3_page_pagetable
673
674	/* Link the l2 -> l3 table */
675	mov	x9, x6
676	adrp	x6, pagetable_l2_ttbr1
677	add	x6, x6, :lo12:pagetable_l2_ttbr1
678	bl	link_l2_pagetable
679#endif
680
681	/* Create the kernel space PTE table */
682	adrp	x6, LL_PAGE_TABLE
683	add	x6, x6, :lo12:LL_PAGE_TABLE
684	ldr	x7, =(ATTR_S1_IDX(VM_MEMATTR_WRITE_BACK) | \
685	    ATTR_S1_AP(ATTR_S1_AP_RO))
686	mov	x8, #(KERNBASE)
687	mov	x9, x28
688	mov	x10, x25
689	bl	BUILD_PTE_FUNC
690
691#if PAGE_SIZE == PAGE_SIZE_4K
692	/* Skip memory mapped through the L2 table */
693	add	x25, x25, #1
694#endif
695
696	/* Create the kernel space XN PTE table */
697	lsl	x10, x25, #(PTE_SHIFT)
698	ldr	x7, =(ATTR_S1_IDX(VM_MEMATTR_WRITE_BACK) | ATTR_S1_XN)
699	ldr	x8, =(KERNBASE)
700	add	x8, x8, x10
701	add	x9, x28, x10
702	sub	x10, x14, x25
703	bl	BUILD_PTE_FUNC
704
705#undef PTE_SHIFT
706#undef LL_PAGE_TABLE
707#undef BUILD_PTE_FUNC
708
709#if PAGE_SIZE != PAGE_SIZE_4K
710	/* Link the l2 -> l3 table */
711	mov	x9, x6
712	adrp	x6, pagetable_l2_ttbr1
713	add	x6, x6, :lo12:pagetable_l2_ttbr1
714	bl	link_l2_pagetable
715#endif
716
717	/* Link the l1 -> l2 table */
718	mov	x9, x6
719	adrp	x6, pagetable_l1_ttbr1
720	add	x6, x6, :lo12:pagetable_l1_ttbr1
721	bl	link_l1_pagetable
722
723	/* Link the l0 -> l1 table */
724	mov	x9, x6
725	adrp	x6, pagetable_l0_ttbr1
726	add	x6, x6, :lo12:pagetable_l0_ttbr1
727	mov	x10, #1
728	bl	link_l0_pagetable
729
730	/* Save the TTBR1 table physical address */
731	mov	x24, x6
732
733	/*
734	 * Build the TTBR0 maps.  As TTBR0 maps, they must specify ATTR_S1_nG.
735	 * They are only needed early on, so the VA = PA map is uncached.
736	 */
737
738	adrp	x6, pagetable_l2_ttbr0_bootstrap
739	add	x6, x6, :lo12:pagetable_l2_ttbr0_bootstrap
740
741	/* Create the VA = PA map */
742	mov	x7, #(ATTR_S1_nG | ATTR_S1_IDX(VM_MEMATTR_WRITE_BACK))
743	adrp	x16, _start
744	and	x16, x16, #(~L2_OFFSET)
745	mov	x9, x16		/* PA start */
746	mov	x8, x16		/* VA start (== PA start) */
747	mov	x10, #1
748	bl	build_l2_block_pagetable
749
750#if defined(SOCDEV_PA)
751	/* Create a table for the UART */
752	mov	x7, #(ATTR_S1_nG | ATTR_S1_IDX(VM_MEMATTR_DEVICE))
753	ldr	x9, =(L2_SIZE)
754	add	x16, x16, x9	/* VA start */
755	mov	x8, x16
756
757	/* Store the socdev virtual address */
758	add	x17, x8, #(SOCDEV_PA & L2_OFFSET)
759	adrp	x9, socdev_va
760	str	x17, [x9, :lo12:socdev_va]
761
762	mov	x9, #(SOCDEV_PA & ~L2_OFFSET)	/* PA start */
763	mov	x10, #1
764	bl	build_l2_block_pagetable
765#endif
766
767#if defined(LINUX_BOOT_ABI)
768	/* Map FDT data ? */
769	cbz	x19, 1f
770
771	/* Create the mapping for FDT data (2 MiB max) */
772	mov	x7, #(ATTR_S1_nG | ATTR_S1_IDX(VM_MEMATTR_WRITE_BACK))
773	ldr	x9, =(L2_SIZE)
774	add	x16, x16, x9	/* VA start */
775	mov	x8, x16
776	mov	x9, x0			/* PA start */
777	/* Update the module pointer to point at the allocated memory */
778	and	x0, x0, #(L2_OFFSET)	/* Keep the lower bits */
779	add	x0, x0, x8		/* Add the aligned virtual address */
780
781	mov	x10, #1
782	bl	build_l2_block_pagetable
783
7841:
785#endif
786
787	/* Link the l1 -> l2 table */
788	mov	x9, x6
789	adrp	x6, pagetable_l1_ttbr0_bootstrap
790	add	x6, x6, :lo12:pagetable_l1_ttbr0_bootstrap
791	bl	link_l1_pagetable
792
793	/* Link the l0 -> l1 table */
794	mov	x9, x6
795	adrp	x6, pagetable_l0_ttbr0_bootstrap
796	add	x6, x6, :lo12:pagetable_l0_ttbr0_bootstrap
797	mov	x10, #1
798	bl	link_l0_pagetable
799
800	/* Save the TTBR0 table physical address */
801	mov	x27, x6
802
803	/* Restore the Link register */
804	mov	x30, x5
805	ret
806LEND(create_pagetables)
807
808/*
809 * Builds an L0 -> L1 table descriptor
810 *
811 *  x6  = L0 table
812 *  x8  = Virtual Address
813 *  x9  = L1 PA (trashed)
814 *  x10 = Entry count (trashed)
815 *  x11, x12 and x13 are trashed
816 */
817LENTRY(link_l0_pagetable)
818	/*
819	 * Link an L0 -> L1 table entry.
820	 */
821	/* Find the table index */
822	lsr	x11, x8, #L0_SHIFT
823	and	x11, x11, #L0_ADDR_MASK
824
825	/* Build the L0 block entry */
826	mov	x12, #L0_TABLE
827	orr	x12, x12, #(TATTR_UXN_TABLE | TATTR_AP_TABLE_NO_EL0)
828
829	/* Only use the output address bits */
830	lsr	x9, x9, #PAGE_SHIFT
8311:	orr	x13, x12, x9, lsl #PAGE_SHIFT
832
833	/* Store the entry */
834	str	x13, [x6, x11, lsl #3]
835
836	sub	x10, x10, #1
837	add	x11, x11, #1
838	add	x9, x9, #1
839	cbnz	x10, 1b
840
841	ret
842LEND(link_l0_pagetable)
843
844/*
845 * Builds an L1 -> L2 table descriptor
846 *
847 *  x6  = L1 table
848 *  x8  = Virtual Address
849 *  x9  = L2 PA (trashed)
850 *  x11, x12 and x13 are trashed
851 */
852LENTRY(link_l1_pagetable)
853	/*
854	 * Link an L1 -> L2 table entry.
855	 */
856	/* Find the table index */
857	lsr	x11, x8, #L1_SHIFT
858	and	x11, x11, #Ln_ADDR_MASK
859
860	/* Build the L1 block entry */
861	mov	x12, #L1_TABLE
862
863	/* Only use the output address bits */
864	lsr	x9, x9, #PAGE_SHIFT
865	orr	x13, x12, x9, lsl #PAGE_SHIFT
866
867	/* Store the entry */
868	str	x13, [x6, x11, lsl #3]
869
870	ret
871LEND(link_l1_pagetable)
872
873/*
874 * Builds count 2 MiB page table entry
875 *  x6  = L2 table
876 *  x7  = Block attributes
877 *  x8  = VA start
878 *  x9  = PA start (trashed)
879 *  x10 = Entry count (trashed)
880 *  x11, x12 and x13 are trashed
881 */
882LENTRY(build_l2_block_pagetable)
883	/*
884	 * Build the L2 table entry.
885	 */
886	/* Find the table index */
887	lsr	x11, x8, #L2_SHIFT
888	and	x11, x11, #Ln_ADDR_MASK
889
890	/* Build the L2 block entry */
891	orr	x12, x7, #L2_BLOCK
892	orr	x12, x12, #(ATTR_AF)
893	orr	x12, x12, #(ATTR_S1_UXN)
894#ifdef __ARM_FEATURE_BTI_DEFAULT
895	orr	x12, x12, x21
896#endif
897	/* Set the shareability attribute */
898	orr	x12, x12, x22
899
900	/* Only use the output address bits */
901	lsr	x9, x9, #L2_SHIFT
902
903	/* Set the physical address for this virtual address */
9041:	orr	x13, x12, x9, lsl #L2_SHIFT
905
906	/* Store the entry */
907	str	x13, [x6, x11, lsl #3]
908
909	sub	x10, x10, #1
910	add	x11, x11, #1
911	add	x9, x9, #1
912	cbnz	x10, 1b
913
914	ret
915LEND(build_l2_block_pagetable)
916
917/*
918 * Builds an L2 -> L3 table descriptor
919 *
920 *  x6  = L2 table
921 *  x8  = Virtual Address
922 *  x9  = L3 PA (trashed)
923 *  x11, x12 and x13 are trashed
924 */
925LENTRY(link_l2_pagetable)
926	/*
927	 * Link an L2 -> L3 table entry.
928	 */
929	/* Find the table index */
930	lsr	x11, x8, #L2_SHIFT
931	and	x11, x11, #Ln_ADDR_MASK
932
933	/* Build the L1 block entry */
934	mov	x12, #L2_TABLE
935
936	/* Only use the output address bits */
937	lsr	x9, x9, #PAGE_SHIFT
938	orr	x13, x12, x9, lsl #PAGE_SHIFT
939
940	/* Store the entry */
941	str	x13, [x6, x11, lsl #3]
942
943	ret
944LEND(link_l2_pagetable)
945
946/*
947 * Builds count level 3 page table entries. Uses ATTR_CONTIGUOUS to create
948 * large page (L3C) mappings when the current VA and remaining count allow
949 * it.
950 *  x6  = L3 table
951 *  x7  = Block attributes
952 *  x8  = VA start
953 *  x9  = PA start (trashed)
954 *  x10 = Entry count (trashed)
955 *  x11, x12 and x13 are trashed
956 *
957 * VA start (x8) modulo L3C_SIZE must equal PA start (x9) modulo L3C_SIZE.
958 */
959LENTRY(build_l3_page_pagetable)
960	cbz	x10, 2f
961	/*
962	 * Build the L3 table entry.
963	 */
964	/* Find the table index */
965	lsr	x11, x8, #L3_SHIFT
966	and	x11, x11, #Ln_ADDR_MASK
967
968	/* Build the L3 page entry */
969	orr	x12, x7, #L3_PAGE
970	orr	x12, x12, #(ATTR_AF)
971	orr	x12, x12, #(ATTR_S1_UXN)
972#ifdef __ARM_FEATURE_BTI_DEFAULT
973	orr	x12, x12, x21
974#endif
975	/* Set the shareability attribute */
976	orr	x12, x12, x22
977
978	/* Only use the output address bits */
979	lsr	x9, x9, #L3_SHIFT
980
981	/* Check if an ATTR_CONTIGUOUS mapping is possible */
9821:	tst	x11, #(L3C_ENTRIES - 1)
983	b.ne	2f
984	cmp	x10, #L3C_ENTRIES
985	b.lo	3f
986	orr	x12, x12, #(ATTR_CONTIGUOUS)
987	b	2f
9883:	and	x12, x12, #(~ATTR_CONTIGUOUS)
989
990	/* Set the physical address for this virtual address */
9912:	orr	x13, x12, x9, lsl #L3_SHIFT
992
993	/* Store the entry */
994	str	x13, [x6, x11, lsl #3]
995
996	sub	x10, x10, #1
997	add	x11, x11, #1
998	add	x9, x9, #1
999	cbnz	x10, 1b
10002:
1001
1002	ret
1003LEND(build_l3_page_pagetable)
1004
1005LENTRY(start_mmu)
1006	dsb	sy
1007
1008	/* Load the exception vectors */
1009	ldr	x2, =exception_vectors
1010	msr	vbar_el1, x2
1011
1012	/* Load ttbr0 and ttbr1 */
1013	msr	ttbr0_el1, x27
1014	msr	ttbr1_el1, x24
1015	isb
1016
1017	/* Clear the Monitor Debug System control register */
1018	msr	mdscr_el1, xzr
1019
1020	/* Invalidate the TLB */
1021	tlbi	vmalle1is
1022	dsb	ish
1023	isb
1024
1025	ldr	x2, mair
1026	msr	mair_el1, x2
1027
1028	/*
1029	 * Setup TCR according to the PARange and ASIDBits fields
1030	 * from ID_AA64MMFR0_EL1 and the HAFDBS field from the
1031	 * ID_AA64MMFR1_EL1.  More precisely, set TCR_EL1.AS
1032	 * to 1 only if the ASIDBits field equals 0b0010.
1033	 */
1034	ldr	x2, tcr
1035
1036	/* If x22 contains a non-zero value then LPA2 is not implemented */
1037	cbnz	x22, .Lno_lpa2
1038	ldr	x3, =(TCR_DS)
1039	orr	x2, x2, x3
1040.Lno_lpa2:
1041
1042	mrs	x3, id_aa64mmfr0_el1
1043
1044	/* Copy the bottom 3 bits from id_aa64mmfr0_el1 into TCR.IPS */
1045	bfi	x2, x3, #(TCR_IPS_SHIFT), #(TCR_IPS_WIDTH)
1046	and	x3, x3, #(ID_AA64MMFR0_ASIDBits_MASK)
1047
1048	/* Check if the HW supports 16 bit ASIDS */
1049	cmp	x3, #(ID_AA64MMFR0_ASIDBits_16)
1050	/* If so x3 == 1, else x3 == 0 */
1051	cset	x3, eq
1052	/* Set TCR.AS with x3 */
1053	bfi	x2, x3, #(TCR_ASID_SHIFT), #(TCR_ASID_WIDTH)
1054
1055	/*
1056	 * Check if the HW supports access flag updates, and set
1057	 * TCR_EL1.HA accordingly. The TCR_EL1.HD flag to enable
1058	 * HW management of dirty state is set in C code as it may
1059	 * need to be disabled because of CPU errata.
1060	 */
1061	CHECK_CPU_FEAT(x3, ID_AA64MMFR1, HAFDBS, AF, 1f)
1062	orr	x2, x2, #(TCR_HA)
10631:
1064
1065	msr	tcr_el1, x2
1066
1067	/*
1068	 * Setup SCTLR.
1069	 */
1070	ldr	x1, =SCTLR_MMU_ON
1071	msr	sctlr_el1, x1
1072	isb
1073
1074	ret
1075
1076	.align 3
1077mair:
1078	.quad	MAIR_ATTR(MAIR_DEVICE_nGnRnE, VM_MEMATTR_DEVICE_nGnRnE) | \
1079		MAIR_ATTR(MAIR_NORMAL_NC, VM_MEMATTR_UNCACHEABLE)   |	\
1080		MAIR_ATTR(MAIR_NORMAL_WB, VM_MEMATTR_WRITE_BACK)    |	\
1081		MAIR_ATTR(MAIR_NORMAL_WT, VM_MEMATTR_WRITE_THROUGH) |	\
1082		MAIR_ATTR(MAIR_DEVICE_nGnRE, VM_MEMATTR_DEVICE_nGnRE)
1083tcr:
1084#if PAGE_SIZE == PAGE_SIZE_4K
1085#define	TCR_TG	(TCR_TG1_4K | TCR_TG0_4K)
1086#elif PAGE_SIZE == PAGE_SIZE_16K
1087#define	TCR_TG	(TCR_TG1_16K | TCR_TG0_16K)
1088#else
1089#error Unsupported page size
1090#endif
1091
1092	.quad (TCR_TxSZ(64 - VIRT_BITS) | TCR_TG |			\
1093	    TCR_SH1_IS | TCR_ORGN1_WBWA | TCR_IRGN1_WBWA |		\
1094	    TCR_SH0_IS | TCR_ORGN0_WBWA | TCR_IRGN0_WBWA)
1095LEND(start_mmu)
1096
1097ENTRY(abort)
1098	b abort
1099END(abort)
1100
1101.bss
1102	.align	PAGE_SHIFT
1103initstack:
1104	.space	BOOT_STACK_SIZE
1105initstack_end:
1106
1107	.section .init_pagetable, "aw", %nobits
1108	.align PAGE_SHIFT
1109	/*
1110	 * 6 initial tables (in the following order):
1111	 *           L2 for kernel (High addresses)
1112	 *           L1 for kernel
1113	 *           L0 for kernel
1114	 *           L1 bootstrap for user   (Low addresses)
1115	 *           L0 bootstrap for user
1116	 *           L0 for user
1117	 */
1118	.globl pagetable_l0_ttbr1
1119pagetable:
1120pagetable_l3_ttbr1:
1121	.space	(PAGE_SIZE * L3_PAGE_COUNT)
1122pagetable_l2_ttbr1:
1123	.space	PAGE_SIZE
1124pagetable_l1_ttbr1:
1125	.space	PAGE_SIZE
1126pagetable_l0_ttbr1:
1127	.space	PAGE_SIZE
1128pagetable_l2_ttbr0_bootstrap:
1129	.space	PAGE_SIZE
1130pagetable_l1_ttbr0_bootstrap:
1131	.space	PAGE_SIZE
1132pagetable_l0_ttbr0_bootstrap:
1133	.space	PAGE_SIZE
1134pagetable_l0_ttbr0:
1135	.space	PAGE_SIZE
1136pagetable_end:
1137
1138el2_pagetable:
1139	.space	PAGE_SIZE
1140
1141	.section .rodata, "a", %progbits
1142	.globl	aarch32_sigcode
1143	.align 2
1144aarch32_sigcode:
1145	.word 0xe1a0000d	// mov r0, sp
1146	.word 0xe2800040	// add r0, r0, #SIGF_UC
1147	.word 0xe59f700c	// ldr r7, [pc, #12]
1148	.word 0xef000000	// swi #0
1149	.word 0xe59f7008	// ldr r7, [pc, #8]
1150	.word 0xef000000	// swi #0
1151	.word 0xeafffffa	// b . - 16
1152	.word SYS_sigreturn
1153	.word SYS_exit
1154	.align	3
1155	.size aarch32_sigcode, . - aarch32_sigcode
1156aarch32_esigcode:
1157	.data
1158	.global sz_aarch32_sigcode
1159sz_aarch32_sigcode:
1160	.quad aarch32_esigcode - aarch32_sigcode
1161
1162GNU_PROPERTY_AARCH64_FEATURE_1_NOTE(GNU_PROPERTY_AARCH64_FEATURE_1_VAL)
1163