xref: /openbmc/linux/arch/x86/boot/compressed/head_64.S (revision 7051924f771722c6dd235e693742cda6488ac700)
1/*
2 *  linux/boot/head.S
3 *
4 *  Copyright (C) 1991, 1992, 1993  Linus Torvalds
5 */
6
7/*
8 *  head.S contains the 32-bit startup code.
9 *
10 * NOTE!!! Startup happens at absolute address 0x00001000, which is also where
11 * the page directory will exist. The startup code will be overwritten by
12 * the page directory. [According to comments etc elsewhere on a compressed
13 * kernel it will end up at 0x1000 + 1Mb I hope so as I assume this. - AC]
14 *
15 * Page 0 is deliberately kept safe, since System Management Mode code in
16 * laptops may need to access the BIOS data stored there.  This is also
17 * useful for future device drivers that either access the BIOS via VM86
18 * mode.
19 */
20
21/*
22 * High loaded stuff by Hans Lermen & Werner Almesberger, Feb. 1996
23 */
24	.code32
25	.text
26
27#include <linux/init.h>
28#include <linux/linkage.h>
29#include <asm/segment.h>
30#include <asm/boot.h>
31#include <asm/msr.h>
32#include <asm/processor-flags.h>
33#include <asm/asm-offsets.h>
34
35/*
36 * Adjust our own GOT
37 *
38 * The relocation base must be in %rbx
39 *
40 * It is safe to call this macro more than once, because in some of the
41 * code paths multiple invocations are inevitable, e.g. via the efi*
42 * entry points.
43 *
44 * Relocation is only performed the first time.
45 */
46.macro FIXUP_GOT
47	cmpb	$1, got_fixed(%rip)
48	je	2f
49
50	leaq	_got(%rip), %rdx
51	leaq	_egot(%rip), %rcx
521:
53	cmpq	%rcx, %rdx
54	jae	2f
55	addq	%rbx, (%rdx)
56	addq	$8, %rdx
57	jmp	1b
582:
59	movb	$1, got_fixed(%rip)
60.endm
61
62	__HEAD
63	.code32
64ENTRY(startup_32)
65	/*
66	 * 32bit entry is 0 and it is ABI so immutable!
67	 * If we come here directly from a bootloader,
68	 * kernel(text+data+bss+brk) ramdisk, zero_page, command line
69	 * all need to be under the 4G limit.
70	 */
71	cld
72	/*
73	 * Test KEEP_SEGMENTS flag to see if the bootloader is asking
74	 * us to not reload segments
75	 */
76	testb $(1<<6), BP_loadflags(%esi)
77	jnz 1f
78
79	cli
80	movl	$(__BOOT_DS), %eax
81	movl	%eax, %ds
82	movl	%eax, %es
83	movl	%eax, %ss
841:
85
86/*
87 * Calculate the delta between where we were compiled to run
88 * at and where we were actually loaded at.  This can only be done
89 * with a short local call on x86.  Nothing  else will tell us what
90 * address we are running at.  The reserved chunk of the real-mode
91 * data at 0x1e4 (defined as a scratch field) are used as the stack
92 * for this calculation. Only 4 bytes are needed.
93 */
94	leal	(BP_scratch+4)(%esi), %esp
95	call	1f
961:	popl	%ebp
97	subl	$1b, %ebp
98
99/* setup a stack and make sure cpu supports long mode. */
100	movl	$boot_stack_end, %eax
101	addl	%ebp, %eax
102	movl	%eax, %esp
103
104	call	verify_cpu
105	testl	%eax, %eax
106	jnz	no_longmode
107
108/*
109 * Compute the delta between where we were compiled to run at
110 * and where the code will actually run at.
111 *
112 * %ebp contains the address we are loaded at by the boot loader and %ebx
113 * contains the address where we should move the kernel image temporarily
114 * for safe in-place decompression.
115 */
116
117#ifdef CONFIG_RELOCATABLE
118	movl	%ebp, %ebx
119	movl	BP_kernel_alignment(%esi), %eax
120	decl	%eax
121	addl	%eax, %ebx
122	notl	%eax
123	andl	%eax, %ebx
124	cmpl	$LOAD_PHYSICAL_ADDR, %ebx
125	jge	1f
126#endif
127	movl	$LOAD_PHYSICAL_ADDR, %ebx
1281:
129
130	/* Target address to relocate to for decompression */
131	addl	$z_extract_offset, %ebx
132
133/*
134 * Prepare for entering 64 bit mode
135 */
136
137	/* Load new GDT with the 64bit segments using 32bit descriptor */
138	leal	gdt(%ebp), %eax
139	movl	%eax, gdt+2(%ebp)
140	lgdt	gdt(%ebp)
141
142	/* Enable PAE mode */
143	movl	%cr4, %eax
144	orl	$X86_CR4_PAE, %eax
145	movl	%eax, %cr4
146
147 /*
148  * Build early 4G boot pagetable
149  */
150	/* Initialize Page tables to 0 */
151	leal	pgtable(%ebx), %edi
152	xorl	%eax, %eax
153	movl	$((4096*6)/4), %ecx
154	rep	stosl
155
156	/* Build Level 4 */
157	leal	pgtable + 0(%ebx), %edi
158	leal	0x1007 (%edi), %eax
159	movl	%eax, 0(%edi)
160
161	/* Build Level 3 */
162	leal	pgtable + 0x1000(%ebx), %edi
163	leal	0x1007(%edi), %eax
164	movl	$4, %ecx
1651:	movl	%eax, 0x00(%edi)
166	addl	$0x00001000, %eax
167	addl	$8, %edi
168	decl	%ecx
169	jnz	1b
170
171	/* Build Level 2 */
172	leal	pgtable + 0x2000(%ebx), %edi
173	movl	$0x00000183, %eax
174	movl	$2048, %ecx
1751:	movl	%eax, 0(%edi)
176	addl	$0x00200000, %eax
177	addl	$8, %edi
178	decl	%ecx
179	jnz	1b
180
181	/* Enable the boot page tables */
182	leal	pgtable(%ebx), %eax
183	movl	%eax, %cr3
184
185	/* Enable Long mode in EFER (Extended Feature Enable Register) */
186	movl	$MSR_EFER, %ecx
187	rdmsr
188	btsl	$_EFER_LME, %eax
189	wrmsr
190
191	/* After gdt is loaded */
192	xorl	%eax, %eax
193	lldt	%ax
194	movl    $0x20, %eax
195	ltr	%ax
196
197	/*
198	 * Setup for the jump to 64bit mode
199	 *
200	 * When the jump is performend we will be in long mode but
201	 * in 32bit compatibility mode with EFER.LME = 1, CS.L = 0, CS.D = 1
202	 * (and in turn EFER.LMA = 1).	To jump into 64bit mode we use
203	 * the new gdt/idt that has __KERNEL_CS with CS.L = 1.
204	 * We place all of the values on our mini stack so lret can
205	 * used to perform that far jump.
206	 */
207	pushl	$__KERNEL_CS
208	leal	startup_64(%ebp), %eax
209#ifdef CONFIG_EFI_MIXED
210	movl	efi32_config(%ebp), %ebx
211	cmp	$0, %ebx
212	jz	1f
213	leal	handover_entry(%ebp), %eax
2141:
215#endif
216	pushl	%eax
217
218	/* Enter paged protected Mode, activating Long Mode */
219	movl	$(X86_CR0_PG | X86_CR0_PE), %eax /* Enable Paging and Protected mode */
220	movl	%eax, %cr0
221
222	/* Jump from 32bit compatibility mode into 64bit mode. */
223	lret
224ENDPROC(startup_32)
225
226#ifdef CONFIG_EFI_MIXED
227	.org 0x190
228ENTRY(efi32_stub_entry)
229	add	$0x4, %esp		/* Discard return address */
230	popl	%ecx
231	popl	%edx
232	popl	%esi
233
234	leal	(BP_scratch+4)(%esi), %esp
235	call	1f
2361:	pop	%ebp
237	subl	$1b, %ebp
238
239	movl	%ecx, efi32_config(%ebp)
240	movl	%edx, efi32_config+8(%ebp)
241	sgdtl	efi32_boot_gdt(%ebp)
242
243	leal	efi32_config(%ebp), %eax
244	movl	%eax, efi_config(%ebp)
245
246	jmp	startup_32
247ENDPROC(efi32_stub_entry)
248#endif
249
250	.code64
251	.org 0x200
252ENTRY(startup_64)
253	/*
254	 * 64bit entry is 0x200 and it is ABI so immutable!
255	 * We come here either from startup_32 or directly from a
256	 * 64bit bootloader.
257	 * If we come here from a bootloader, kernel(text+data+bss+brk),
258	 * ramdisk, zero_page, command line could be above 4G.
259	 * We depend on an identity mapped page table being provided
260	 * that maps our entire kernel(text+data+bss+brk), zero page
261	 * and command line.
262	 */
263#ifdef CONFIG_EFI_STUB
264	/*
265	 * The entry point for the PE/COFF executable is efi_pe_entry, so
266	 * only legacy boot loaders will execute this jmp.
267	 */
268	jmp	preferred_addr
269
270ENTRY(efi_pe_entry)
271	movq	%rcx, efi64_config(%rip)	/* Handle */
272	movq	%rdx, efi64_config+8(%rip) /* EFI System table pointer */
273
274	leaq	efi64_config(%rip), %rax
275	movq	%rax, efi_config(%rip)
276
277	call	1f
2781:	popq	%rbp
279	subq	$1b, %rbp
280
281	/*
282	 * Relocate efi_config->call() and the GOT entries.
283	 */
284	addq	%rbp, efi64_config+88(%rip)
285
286	movq	%rbp, %rbx
287	FIXUP_GOT
288
289	movq	%rax, %rdi
290	call	make_boot_params
291	cmpq	$0,%rax
292	je	fail
293	mov	%rax, %rsi
294	leaq	startup_32(%rip), %rax
295	movl	%eax, BP_code32_start(%rsi)
296	jmp	2f		/* Skip the relocation */
297
298handover_entry:
299	call	1f
3001:	popq	%rbp
301	subq	$1b, %rbp
302
303	/*
304	 * Relocate efi_config->call() and the GOT entries.
305	 */
306	movq	efi_config(%rip), %rax
307	addq	%rbp, 88(%rax)
308
309	movq	%rbp, %rbx
310	FIXUP_GOT
3112:
312	movq	efi_config(%rip), %rdi
313	call	efi_main
314	movq	%rax,%rsi
315	cmpq	$0,%rax
316	jne	2f
317fail:
318	/* EFI init failed, so hang. */
319	hlt
320	jmp	fail
3212:
322	movl	BP_code32_start(%esi), %eax
323	leaq	preferred_addr(%rax), %rax
324	jmp	*%rax
325
326preferred_addr:
327#endif
328
329	/* Setup data segments. */
330	xorl	%eax, %eax
331	movl	%eax, %ds
332	movl	%eax, %es
333	movl	%eax, %ss
334	movl	%eax, %fs
335	movl	%eax, %gs
336
337	/*
338	 * Compute the decompressed kernel start address.  It is where
339	 * we were loaded at aligned to a 2M boundary. %rbp contains the
340	 * decompressed kernel start address.
341	 *
342	 * If it is a relocatable kernel then decompress and run the kernel
343	 * from load address aligned to 2MB addr, otherwise decompress and
344	 * run the kernel from LOAD_PHYSICAL_ADDR
345	 *
346	 * We cannot rely on the calculation done in 32-bit mode, since we
347	 * may have been invoked via the 64-bit entry point.
348	 */
349
350	/* Start with the delta to where the kernel will run at. */
351#ifdef CONFIG_RELOCATABLE
352	leaq	startup_32(%rip) /* - $startup_32 */, %rbp
353	movl	BP_kernel_alignment(%rsi), %eax
354	decl	%eax
355	addq	%rax, %rbp
356	notq	%rax
357	andq	%rax, %rbp
358	cmpq	$LOAD_PHYSICAL_ADDR, %rbp
359	jge	1f
360#endif
361	movq	$LOAD_PHYSICAL_ADDR, %rbp
3621:
363
364	/* Target address to relocate to for decompression */
365	leaq	z_extract_offset(%rbp), %rbx
366
367	/* Set up the stack */
368	leaq	boot_stack_end(%rbx), %rsp
369
370	/* Zero EFLAGS */
371	pushq	$0
372	popfq
373
374/*
375 * Copy the compressed kernel to the end of our buffer
376 * where decompression in place becomes safe.
377 */
378	pushq	%rsi
379	leaq	(_bss-8)(%rip), %rsi
380	leaq	(_bss-8)(%rbx), %rdi
381	movq	$_bss /* - $startup_32 */, %rcx
382	shrq	$3, %rcx
383	std
384	rep	movsq
385	cld
386	popq	%rsi
387
388/*
389 * Jump to the relocated address.
390 */
391	leaq	relocated(%rbx), %rax
392	jmp	*%rax
393
394#ifdef CONFIG_EFI_STUB
395	.org 0x390
396ENTRY(efi64_stub_entry)
397	movq	%rdi, efi64_config(%rip)	/* Handle */
398	movq	%rsi, efi64_config+8(%rip) /* EFI System table pointer */
399
400	leaq	efi64_config(%rip), %rax
401	movq	%rax, efi_config(%rip)
402
403	movq	%rdx, %rsi
404	jmp	handover_entry
405ENDPROC(efi64_stub_entry)
406#endif
407
408	.text
409relocated:
410
411/*
412 * Clear BSS (stack is currently empty)
413 */
414	xorl	%eax, %eax
415	leaq    _bss(%rip), %rdi
416	leaq    _ebss(%rip), %rcx
417	subq	%rdi, %rcx
418	shrq	$3, %rcx
419	rep	stosq
420
421	FIXUP_GOT
422
423/*
424 * Do the decompression, and jump to the new kernel..
425 */
426	pushq	%rsi			/* Save the real mode argument */
427	movq	%rsi, %rdi		/* real mode address */
428	leaq	boot_heap(%rip), %rsi	/* malloc area for uncompression */
429	leaq	input_data(%rip), %rdx  /* input_data */
430	movl	$z_input_len, %ecx	/* input_len */
431	movq	%rbp, %r8		/* output target address */
432	movq	$z_output_len, %r9	/* decompressed length */
433	call	decompress_kernel	/* returns kernel location in %rax */
434	popq	%rsi
435
436/*
437 * Jump to the decompressed kernel.
438 */
439	jmp	*%rax
440
441	.code32
442no_longmode:
443	/* This isn't an x86-64 CPU so hang */
4441:
445	hlt
446	jmp     1b
447
448#include "../../kernel/verify_cpu.S"
449
450	.data
451gdt:
452	.word	gdt_end - gdt
453	.long	gdt
454	.word	0
455	.quad	0x0000000000000000	/* NULL descriptor */
456	.quad	0x00af9a000000ffff	/* __KERNEL_CS */
457	.quad	0x00cf92000000ffff	/* __KERNEL_DS */
458	.quad	0x0080890000000000	/* TS descriptor */
459	.quad   0x0000000000000000	/* TS continued */
460gdt_end:
461
462/* Have we relocated the GOT? */
463got_fixed:
464	.byte	0
465
466#ifdef CONFIG_EFI_STUB
467efi_config:
468	.quad	0
469
470#ifdef CONFIG_EFI_MIXED
471	.global efi32_config
472efi32_config:
473	.fill	11,8,0
474	.quad	efi64_thunk
475	.byte	0
476#endif
477
478	.global efi64_config
479efi64_config:
480	.fill	11,8,0
481	.quad	efi_call
482	.byte	1
483#endif /* CONFIG_EFI_STUB */
484
485/*
486 * Stack and heap for uncompression
487 */
488	.bss
489	.balign 4
490boot_heap:
491	.fill BOOT_HEAP_SIZE, 1, 0
492boot_stack:
493	.fill BOOT_STACK_SIZE, 1, 0
494boot_stack_end:
495
496/*
497 * Space for page tables (not in .bss so not zeroed)
498 */
499	.section ".pgtable","a",@nobits
500	.balign 4096
501pgtable:
502	.fill 6*4096, 1, 0
503