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