1#include <xen/lib.h>
2#include <xen/multiboot.h>
3#include <xen/multiboot2.h>
4#include <public/xen.h>
5#include <asm/asm_defns.h>
6#include <asm/fixmap.h>
7#include <asm/page.h>
8#include <asm/processor.h>
9#include <asm/msr-index.h>
10#include <asm/cpufeature.h>
11#include <public/elfnote.h>
12
13        .section .text.header, "ax", @progbits
14        .code32
15
16#define sym_offs(sym)     ((sym) - __XEN_VIRT_START)
17#define sym_esi(sym)      sym_offs(sym)(%esi)
18
19#define BOOT_CS32        0x0008
20#define BOOT_CS64        0x0010
21#define BOOT_DS          0x0018
22#define BOOT_PSEUDORM_CS 0x0020
23#define BOOT_PSEUDORM_DS 0x0028
24
25#define MB2_HT(name)      (MULTIBOOT2_HEADER_TAG_##name)
26#define MB2_TT(name)      (MULTIBOOT2_TAG_TYPE_##name)
27
28        .macro mb2ht_args arg:req, args:vararg
29        .long \arg
30        .ifnb \args
31        mb2ht_args \args
32        .endif
33        .endm
34
35        .macro mb2ht_init type:req, req:req, args:vararg
36        .balign MULTIBOOT2_TAG_ALIGN, 0xc2 /* Avoid padding with long nops. */
37.Lmb2ht_init_start\@:
38        .short \type
39        .short \req
40        .long .Lmb2ht_init_end\@ - .Lmb2ht_init_start\@
41        .ifnb \args
42        mb2ht_args \args
43        .endif
44.Lmb2ht_init_end\@:
45        .endm
46
47ENTRY(start)
48        jmp     __start
49
50        .balign 4
51multiboot1_header:             /*** MULTIBOOT1 HEADER ****/
52#define MULTIBOOT_HEADER_FLAGS (MULTIBOOT_HEADER_MODS_ALIGNED | \
53                                MULTIBOOT_HEADER_WANT_MEMORY)
54        /* Magic number indicating a Multiboot header. */
55        .long   MULTIBOOT_HEADER_MAGIC
56        /* Flags to bootloader (see Multiboot spec). */
57        .long   MULTIBOOT_HEADER_FLAGS
58        /* Checksum: must be the negated sum of the first two fields. */
59        .long   -(MULTIBOOT_HEADER_MAGIC + MULTIBOOT_HEADER_FLAGS)
60
61        .size multiboot1_header, . - multiboot1_header
62        .type multiboot1_header, @object
63
64/*** MULTIBOOT2 HEADER ****/
65/* Some ideas are taken from grub-2.00/grub-core/tests/boot/kernel-i386.S file. */
66        .balign MULTIBOOT2_HEADER_ALIGN, 0xc2  /* Avoid padding the MB1 header with long nops. */
67
68multiboot2_header:
69        /* Magic number indicating a Multiboot2 header. */
70        .long   MULTIBOOT2_HEADER_MAGIC
71        /* Architecture: i386. */
72        .long   MULTIBOOT2_ARCHITECTURE_I386
73        /* Multiboot2 header length. */
74        .long   .Lmultiboot2_header_end - multiboot2_header
75        /* Multiboot2 header checksum. */
76        .long   -(MULTIBOOT2_HEADER_MAGIC + MULTIBOOT2_ARCHITECTURE_I386 + \
77                        (.Lmultiboot2_header_end - multiboot2_header))
78
79        /* Multiboot2 information request tag. */
80        mb2ht_init MB2_HT(INFORMATION_REQUEST), MB2_HT(REQUIRED), \
81                   MB2_TT(BASIC_MEMINFO), MB2_TT(MMAP)
82
83        /* Align modules at page boundry. */
84        mb2ht_init MB2_HT(MODULE_ALIGN), MB2_HT(REQUIRED)
85
86        /* Load address preference. */
87        mb2ht_init MB2_HT(RELOCATABLE), MB2_HT(OPTIONAL), \
88                   sym_offs(start), /* Min load address. */ \
89                   0xffffffff, /* The end of image max load address (4 GiB - 1). */ \
90                   0x200000, /* Load address alignment (2 MiB). */ \
91                   MULTIBOOT2_LOAD_PREFERENCE_HIGH
92
93        /* Console flags tag. */
94        mb2ht_init MB2_HT(CONSOLE_FLAGS), MB2_HT(OPTIONAL), \
95                   MULTIBOOT2_CONSOLE_FLAGS_EGA_TEXT_SUPPORTED
96
97        /* Framebuffer tag. */
98        mb2ht_init MB2_HT(FRAMEBUFFER), MB2_HT(OPTIONAL), \
99                   0, /* Number of the columns - no preference. */ \
100                   0, /* Number of the lines - no preference. */ \
101                   0  /* Number of bits per pixel - no preference. */
102
103        /* Request that ExitBootServices() not be called. */
104        mb2ht_init MB2_HT(EFI_BS), MB2_HT(OPTIONAL)
105
106        /* EFI64 Multiboot2 entry point. */
107        mb2ht_init MB2_HT(ENTRY_ADDRESS_EFI64), MB2_HT(OPTIONAL), \
108                   sym_offs(__efi64_mb2_start)
109
110        /* Multiboot2 header end tag. */
111        mb2ht_init MB2_HT(END), MB2_HT(REQUIRED)
112.Lmultiboot2_header_end:
113
114        .size multiboot2_header, . - multiboot2_header
115        .type multiboot2_header, @object
116
117        .section .init.rodata, "a", @progbits
118
119.Lbad_cpu_msg: .asciz "ERR: Not a 64-bit CPU!"
120.Lbad_ldr_msg: .asciz "ERR: Not a Multiboot bootloader!"
121.Lbad_ldr_nbs: .asciz "ERR: Bootloader shutdown EFI x64 boot services!"
122.Lbad_ldr_nst: .asciz "ERR: EFI SystemTable is not provided by bootloader!"
123.Lbad_ldr_nih: .asciz "ERR: EFI ImageHandle is not provided by bootloader!"
124.Lbad_efi_msg: .asciz "ERR: EFI IA-32 platforms are not supported!"
125.Lbag_alg_msg: .asciz "ERR: Xen must be loaded at a 2Mb boundary!"
126.Lno_nx_msg:   .asciz "ERR: Not an NX-capable CPU!"
127
128        .section .init.data, "aw", @progbits
129        .align 4
130
131        .word   0
132gdt_boot_descr:
133        .word   .Ltrampoline_gdt_end - trampoline_gdt - 1
134gdt_boot_base:
135        .long   sym_offs(trampoline_gdt)
136        .long   0 /* Needed for 64-bit lgdt */
137
138vga_text_buffer:
139        .long   0xb8000
140
141efi_platform:
142        .byte   0
143
144        .section .init.text, "ax", @progbits
145
146early_error: /* Here to improve the disassembly. */
147
148.Lbad_cpu:
149        mov     $sym_offs(.Lbad_cpu_msg), %ecx
150        jmp     .Lget_vtb
151.Lnot_multiboot:
152        mov     $sym_offs(.Lbad_ldr_msg), %ecx
153        jmp     .Lget_vtb
154.Lnot_aligned:
155        mov     $sym_offs(.Lbag_alg_msg), %ecx
156        jmp     .Lget_vtb
157#ifdef CONFIG_REQUIRE_NX
158.Lno_nx:
159        mov     $sym_offs(.Lno_nx_msg), %ecx
160        jmp     .Lget_vtb
161#endif
162.Lmb2_no_st:
163        /*
164         * Here we are on EFI platform. vga_text_buffer was zapped earlier
165         * because there is pretty good chance that VGA is unavailable.
166         */
167        mov     $sym_offs(.Lbad_ldr_nst), %ecx
168        jmp     .Lget_vtb
169.Lmb2_no_ih:
170        /* Ditto. */
171        mov     $sym_offs(.Lbad_ldr_nih), %ecx
172        jmp     .Lget_vtb
173.Lmb2_no_bs:
174        /*
175         * Ditto. Additionally, here there is a chance that Xen was started
176         * via start label. Then reliable vga_text_buffer zap is impossible
177         * in Multiboot2 scanning loop and we have to zero %edi below.
178         */
179        mov     $sym_offs(.Lbad_ldr_nbs), %ecx
180        xor     %edi,%edi                       # No VGA text buffer
181        jmp     .Lprint_err
182.Lmb2_efi_ia_32:
183        /*
184         * Here we are on EFI IA-32 platform. Then reliable vga_text_buffer zap is
185         * impossible in Multiboot2 scanning loop and we have to zero %edi below.
186         */
187        mov     $sym_offs(.Lbad_efi_msg), %ecx
188        xor     %edi,%edi                       # No VGA text buffer
189        jmp     .Lprint_err
190.Lget_vtb:
191        mov     sym_esi(vga_text_buffer), %edi
192.Lprint_err:
193        add     %ecx, %esi     # Add string offset to relocation base.
194        # NOTE: No further use of sym_esi() till the end of the "function"!
1951:
196        lodsb
197        test    %al,%al        # Terminate on '\0' sentinel
198        je      .Lhalt
199        mov     $0x3f8+5,%dx   # UART Line Status Register
200        mov     %al,%bl
2012:      in      %dx,%al
202        test    $0x20,%al      # Test THR Empty flag
203        je      2b
204        mov     $0x3f8+0,%dx   # UART Transmit Holding Register
205        mov     %bl,%al
206        out     %al,%dx        # Send a character over the serial line
207        test    %edi,%edi      # Is the VGA text buffer available?
208        jz      1b
209        stosb                  # Write a character to the VGA text buffer
210        mov     $7,%al
211        stosb                  # Write an attribute to the VGA text buffer
212        jmp     1b
213.Lhalt: hlt
214        jmp     .Lhalt
215
216        .size early_error, . - early_error
217        .type early_error, @function
218
219        .code64
220
221__efi64_mb2_start:
222        /*
223         * Multiboot2 spec says that here CPU is in 64-bit mode. However,
224         * there is also guarantee that all code and data is always put
225         * by the bootloader below 4 GiB. Hence, we can safely truncate
226         * addresses to 32-bits in most cases below.
227         */
228
229        cld
230
231        /* VGA is not available on EFI platforms. */
232        movl   $0,vga_text_buffer(%rip)
233
234        /* Check for Multiboot2 bootloader. */
235        cmp     $MULTIBOOT2_BOOTLOADER_MAGIC,%eax
236        je      .Lefi_multiboot2_proto
237
238        /* Jump to .Lnot_multiboot after switching CPU to x86_32 mode. */
239        lea     .Lnot_multiboot(%rip), %r15
240        jmp     x86_32_switch
241
242.Lefi_multiboot2_proto:
243        /* Zero EFI SystemTable, EFI ImageHandle addresses and cmdline. */
244        xor     %esi,%esi
245        xor     %edi,%edi
246        xor     %edx,%edx
247
248        /* Skip Multiboot2 information fixed part. */
249        lea     (MB2_fixed_sizeof+MULTIBOOT2_TAG_ALIGN-1)(%rbx),%ecx
250        and     $~(MULTIBOOT2_TAG_ALIGN-1),%ecx
251
252.Lefi_mb2_tsize:
253        /* Check Multiboot2 information total size. */
254        mov     %ecx,%r8d
255        sub     %ebx,%r8d
256        cmp     %r8d,MB2_fixed_total_size(%rbx)
257        jbe     .Lrun_bs
258
259        /* Are EFI boot services available? */
260        cmpl    $MULTIBOOT2_TAG_TYPE_EFI_BS,MB2_tag_type(%rcx)
261        jne     .Lefi_mb2_st
262
263        /* We are on EFI platform and EFI boot services are available. */
264        incb    efi_platform(%rip)
265
266        /*
267         * Disable real mode and other legacy stuff which should not
268         * be run on EFI platforms.
269         */
270        incb    skip_realmode(%rip)
271        jmp     .Lefi_mb2_next_tag
272
273.Lefi_mb2_st:
274        /* Get EFI SystemTable address from Multiboot2 information. */
275        cmpl    $MULTIBOOT2_TAG_TYPE_EFI64,MB2_tag_type(%rcx)
276        cmove   MB2_efi64_st(%rcx),%rsi
277        je      .Lefi_mb2_next_tag
278
279        /* Get EFI ImageHandle address from Multiboot2 information. */
280        cmpl    $MULTIBOOT2_TAG_TYPE_EFI64_IH,MB2_tag_type(%rcx)
281        cmove   MB2_efi64_ih(%rcx),%rdi
282        je      .Lefi_mb2_next_tag
283
284        /* Get command line from Multiboot2 information. */
285        cmpl    $MULTIBOOT2_TAG_TYPE_CMDLINE, MB2_tag_type(%rcx)
286        jne     .Lno_cmdline
287        lea     MB2_tag_string(%rcx), %rdx
288        jmp     .Lefi_mb2_next_tag
289.Lno_cmdline:
290
291        /* Is it the end of Multiboot2 information? */
292        cmpl    $MULTIBOOT2_TAG_TYPE_END,MB2_tag_type(%rcx)
293        je      .Lrun_bs
294
295.Lefi_mb2_next_tag:
296        /* Go to next Multiboot2 information tag. */
297        add     MB2_tag_size(%rcx),%ecx
298        add     $(MULTIBOOT2_TAG_ALIGN-1),%ecx
299        and     $~(MULTIBOOT2_TAG_ALIGN-1),%ecx
300        jmp     .Lefi_mb2_tsize
301
302.Lrun_bs:
303        /* Are EFI boot services available? */
304        cmpb    $0,efi_platform(%rip)
305
306        /* Jump to .Lmb2_no_bs after switching CPU to x86_32 mode. */
307        lea     .Lmb2_no_bs(%rip),%r15
308        jz      x86_32_switch
309
310        /* Is EFI SystemTable address provided by boot loader? */
311        test    %rsi,%rsi
312
313        /* Jump to .Lmb2_no_st after switching CPU to x86_32 mode. */
314        lea     .Lmb2_no_st(%rip),%r15
315        jz      x86_32_switch
316
317        /* Is EFI ImageHandle address provided by boot loader? */
318        test    %rdi,%rdi
319
320        /* Jump to .Lmb2_no_ih after switching CPU to x86_32 mode. */
321        lea     .Lmb2_no_ih(%rip),%r15
322        jz      x86_32_switch
323
324        /*
325         * Align the stack as UEFI spec requires. Keep it aligned
326         * before efi_multiboot2() call by pushing/popping even
327         * numbers of items on it.
328         */
329        and     $~15,%rsp
330
331        /* Save Multiboot2 magic on the stack. */
332        push    %rax
333
334        /* Save EFI ImageHandle on the stack. */
335        push    %rdi
336
337        /*
338         * Initialize BSS (no nasty surprises!).
339         * It must be done earlier than in BIOS case
340         * because efi_multiboot2() touches it.
341         */
342        lea     __bss_start(%rip),%edi
343        lea     __bss_end(%rip),%ecx
344        sub     %edi,%ecx
345        shr     $3,%ecx
346        xor     %eax,%eax
347        rep stosq
348
349        /* Keep the stack aligned. Do not pop a single item off it. */
350        mov     (%rsp),%rdi
351
352        /*
353         * efi_multiboot2() is called according to System V AMD64 ABI:
354         *   - IN:  %rdi - EFI ImageHandle, %rsi - EFI SystemTable,
355         *          %rdx - MB2 cmdline
356         */
357        call    efi_multiboot2
358
359        /* Just pop an item from the stack. */
360        pop     %rax
361
362        /* Restore Multiboot2 magic. */
363        pop     %rax
364
365        /* Jump to trampoline_setup after switching CPU to x86_32 mode. */
366        lea     trampoline_setup(%rip),%r15
367
368x86_32_switch:
369        mov     %r15,%rdi
370
371        /* Store Xen image load base address in place accessible for 32-bit code. */
372        lea     __image_base__(%rip),%esi
373
374        cli
375
376        /* Initialize GDTR. */
377        add     %esi,gdt_boot_base(%rip)
378        lgdt    gdt_boot_descr(%rip)
379
380        /* Reload code selector. */
381        pushq   $BOOT_CS32
382        lea     cs32_switch(%rip),%edx
383        push    %rdx
384        lretq
385
386        .code32
387
388cs32_switch:
389        /* Initialize basic data segments. */
390        mov     $BOOT_DS,%edx
391        mov     %edx,%ds
392        mov     %edx,%es
393        mov     %edx,%ss
394        /* %esp is initialized later. */
395
396        /* Load null descriptor to unused segment registers. */
397        xor     %edx,%edx
398        mov     %edx,%fs
399        mov     %edx,%gs
400
401        /* Disable paging. */
402        mov     %cr0,%edx
403        and     $(~X86_CR0_PG),%edx
404        mov     %edx,%cr0
405
406        /* Jump to earlier loaded address. */
407        jmp     *%edi
408
409#ifdef CONFIG_PVH_GUEST
410ELFNOTE(Xen, XEN_ELFNOTE_PHYS32_ENTRY, .long sym_offs(__pvh_start))
411
412__pvh_start:
413        cld
414        cli
415
416        /*
417         * We need one push/pop to determine load address.  Use the same
418         * absolute stack address as the native path, for lack of a better
419         * alternative.
420         */
421        mov     $0x1000, %esp
422
423        /* Calculate the load base address. */
424        call    1f
4251:      pop     %esi
426        sub     $sym_offs(1b), %esi
427
428        /* Set up stack. */
429        lea     STACK_SIZE - CPUINFO_sizeof + sym_esi(cpu0_stack), %esp
430
431        mov     %ebx, sym_esi(pvh_start_info_pa)
432
433        /* Force xen console.  Will revert to user choice in init code. */
434        movb    $-1, sym_esi(opt_console_xen)
435
436        /* Prepare gdt and segments */
437        add     %esi, sym_esi(gdt_boot_base)
438        lgdt    sym_esi(gdt_boot_descr)
439
440        mov     $BOOT_DS, %ecx
441        mov     %ecx, %ds
442        mov     %ecx, %es
443        mov     %ecx, %ss
444
445        /* Skip bootloader setup and bios setup, go straight to trampoline */
446        movb    $1, sym_esi(pvh_boot)
447        movb    $1, sym_esi(skip_realmode)
448
449        /* Set trampoline_phys to use mfn 1 to avoid having a mapping at VA 0 */
450        movw    $0x1000, sym_esi(trampoline_phys)
451        mov     (%ebx), %eax /* mov $XEN_HVM_START_MAGIC_VALUE, %eax */
452        jmp     trampoline_setup
453
454#endif /* CONFIG_PVH_GUEST */
455
456__start:
457        cld
458        cli
459
460        /*
461         * Multiboot (both 1 and 2) specify the stack pointer as undefined
462         * when entering in BIOS circumstances.  This is unhelpful for
463         * relocatable images, where one push/pop is required to calculate
464         * images load address.
465         *
466         * On a BIOS-based system, the IVT and BDA occupy the first 5/16ths of
467         * the first page of RAM, with the rest free for use.  Use the top of
468         * this page for a temporary stack, being one of the safest locations
469         * to clobber.
470         */
471        mov     $0x1000, %esp
472
473        /* Calculate the load base address. */
474        call    1f
4751:      pop     %esi
476        sub     $sym_offs(1b), %esi
477
478        /* Set up stack. */
479        lea     STACK_SIZE - CPUINFO_sizeof + sym_esi(cpu0_stack), %esp
480
481        /* Bootloaders may set multiboot{1,2}.mem_lower to a nonzero value. */
482        xor     %edx,%edx
483
484        /* Check for Multiboot2 bootloader. */
485        cmp     $MULTIBOOT2_BOOTLOADER_MAGIC,%eax
486        je      .Lmultiboot2_proto
487
488        /* Check for Multiboot bootloader. */
489        cmp     $MULTIBOOT_BOOTLOADER_MAGIC,%eax
490        jne     .Lnot_multiboot
491
492        /* Get mem_lower from Multiboot information. */
493        testb   $MBI_MEMLIMITS,MB_flags(%ebx)
494
495        /* Not available? BDA value will be fine. */
496        cmovnz  MB_mem_lower(%ebx),%edx
497        jmp     trampoline_bios_setup
498
499.Lmultiboot2_proto:
500        /* Skip Multiboot2 information fixed part. */
501        lea     (MB2_fixed_sizeof+MULTIBOOT2_TAG_ALIGN-1)(%ebx),%ecx
502        and     $~(MULTIBOOT2_TAG_ALIGN-1),%ecx
503
504.Lmb2_tsize:
505        /* Check Multiboot2 information total size. */
506        mov     %ecx,%edi
507        sub     %ebx,%edi
508        cmp     %edi,MB2_fixed_total_size(%ebx)
509        jbe     trampoline_bios_setup
510
511        /* Get mem_lower from Multiboot2 information. */
512        cmpl    $MULTIBOOT2_TAG_TYPE_BASIC_MEMINFO,MB2_tag_type(%ecx)
513        cmove   MB2_mem_lower(%ecx),%edx
514        je      .Lmb2_next_tag
515
516        /* EFI IA-32 platforms are not supported. */
517        cmpl    $MULTIBOOT2_TAG_TYPE_EFI32,MB2_tag_type(%ecx)
518        je      .Lmb2_efi_ia_32
519
520        /* Bootloader shutdown EFI x64 boot services. */
521        cmpl    $MULTIBOOT2_TAG_TYPE_EFI64,MB2_tag_type(%ecx)
522        je      .Lmb2_no_bs
523
524        /* Is it the end of Multiboot2 information? */
525        cmpl    $MULTIBOOT2_TAG_TYPE_END,MB2_tag_type(%ecx)
526        je      trampoline_bios_setup
527
528.Lmb2_next_tag:
529        /* Go to next Multiboot2 information tag. */
530        add     MB2_tag_size(%ecx),%ecx
531        add     $(MULTIBOOT2_TAG_ALIGN-1),%ecx
532        and     $~(MULTIBOOT2_TAG_ALIGN-1),%ecx
533        jmp     .Lmb2_tsize
534
535trampoline_bios_setup:
536        /*
537         * Called on legacy BIOS platforms only.
538         *
539         * Initialize GDTR and basic data segments.
540         */
541        add     %esi,sym_esi(gdt_boot_base)
542        lgdt    sym_esi(gdt_boot_descr)
543
544        mov     $BOOT_DS,%ecx
545        mov     %ecx,%ds
546        mov     %ecx,%es
547        mov     %ecx,%ss
548        /* %esp is initialized later. */
549
550        /* Load null descriptor to unused segment registers. */
551        xor     %ecx,%ecx
552        mov     %ecx,%fs
553        mov     %ecx,%gs
554
555        /* Set up trampoline segment 64k below EBDA */
556        movzwl  0x40e,%ecx          /* EBDA segment */
557        cmp     $0xa000,%ecx        /* sanity check (high) */
558        jae     0f
559        cmp     $0x4000,%ecx        /* sanity check (low) */
560        jae     1f
5610:
562        movzwl  0x413,%ecx          /* use base memory size on failure */
563        shl     $10-4,%ecx
5641:
565        /*
566         * Compare the value in the BDA with the information from the
567         * multiboot structure (if available) and use the smallest.
568         */
569        cmp     $0x100,%edx         /* is the multiboot value too small? */
570        jb      2f                  /* if so, do not use it */
571        shl     $10-4,%edx
572        cmp     %ecx,%edx           /* compare with BDA value */
573        cmovb   %edx,%ecx           /* and use the smaller */
574
5752:
576        /* Reserve memory for the trampoline and the low-memory stack. */
577        sub     $((TRAMPOLINE_SPACE+TRAMPOLINE_STACK_SPACE)>>4),%ecx
578
579        /* From arch/x86/smpboot.c: start_eip had better be page-aligned! */
580        xor     %cl, %cl
581        shl     $4, %ecx
582        mov     %ecx,sym_esi(trampoline_phys)
583
584trampoline_setup:
585        /*
586         * Called on legacy BIOS and EFI platforms.
587         */
588
589        /* Save Xen image load base address for later use. */
590        mov     %esi, sym_esi(xen_phys_start)
591        mov     %esi, sym_esi(trampoline_xen_phys_start)
592
593        /* Get bottom-most low-memory stack address. */
594        mov     sym_esi(trampoline_phys), %ecx
595        add     $TRAMPOLINE_SPACE,%ecx
596
597#ifdef CONFIG_VIDEO
598        lea     sym_esi(boot_vid_info), %edx
599#else
600        xor     %edx, %edx
601#endif
602
603        /* Save Multiboot / PVH info struct (after relocation) for later use. */
604        push    %edx                /* Boot video info to be filled from MB2. */
605        push    %ecx                /* Bottom-most low-memory stack address. */
606        push    %ebx                /* Multiboot / PVH information address. */
607        push    %eax                /* Magic number. */
608        call    reloc
609#ifdef CONFIG_PVH_GUEST
610        cmpb    $0, sym_esi(pvh_boot)
611        je      1f
612        mov     %eax, sym_esi(pvh_start_info_pa)
613        jmp     2f
614#endif
6151:
616        mov     %eax, sym_esi(multiboot_ptr)
6172:
618
619        /*
620         * Now trampoline_phys points to the following structure (lowest address
621         * is at the bottom):
622         *
623         * +------------------------+
624         * | TRAMPOLINE_STACK_SPACE |
625         * +------------------------+
626         * |     Data (MBI / PVH)   |
627         * +- - - - - - - - - - - - +
628         * |    TRAMPOLINE_SPACE    |
629         * +------------------------+
630         *
631         * Data grows downwards from the highest address of TRAMPOLINE_SPACE
632         * region to the end of the trampoline. The rest of TRAMPOLINE_SPACE is
633         * reserved for trampoline code and data.
634         */
635
636        /*
637         * Do not zero BSS on EFI platform here.
638         * It was initialized earlier.
639         */
640        cmpb    $0, sym_esi(efi_platform)
641        jnz     1f
642
643        /*
644         * Initialise the BSS.
645         *
646         * !!! WARNING - also zeroes the current stack !!!
647         */
648        lea     sym_esi(__bss_start), %edi
649        lea     sym_esi(__bss_end), %ecx
650        sub     %edi,%ecx
651        xor     %eax,%eax
652        shr     $2,%ecx
653        rep stosl
654
6551:
656        /* Interrogate CPU extended features via CPUID. */
657        mov     $1, %eax
658        cpuid
659        mov     %ecx, CPUINFO_FEATURE_OFFSET(X86_FEATURE_HYPERVISOR) + sym_esi(boot_cpu_data)
660
661        mov     $0x80000000,%eax
662        cpuid
663        shld    $16,%eax,%ecx
664        xor     %edx,%edx
665        cmp     $0x8000,%cx         # any function @ 0x8000xxxx?
666        jne     1f
667        cmp     $0x80000000,%eax    # any function > 0x80000000?
668        jbe     1f
669        mov     $0x80000001,%eax
670        cpuid
6711:      mov     %edx, CPUINFO_FEATURE_OFFSET(X86_FEATURE_LM) + sym_esi(boot_cpu_data)
672
673        /* Check for availability of long mode. */
674        bt      $cpufeat_bit(X86_FEATURE_LM),%edx
675        jnc     .Lbad_cpu
676
677        /*
678         * Check for NX
679         *   - If Xen was compiled requiring it simply assert it's
680         *     supported. The trampoline already has the right constant.
681         *   - Otherwise, update the trampoline EFER mask accordingly.
682         */
683        bt      $cpufeat_bit(X86_FEATURE_NX), %edx
684        jc     .Lgot_nx
685
686        /*
687         * NX appears to be unsupported, but it might be hidden.
688         *
689         * The feature is part of the AMD64 spec, but the very first Intel
690         * 64bit CPUs lacked the feature, and thereafter there was a
691         * firmware knob to disable the feature. Undo the disable if
692         * possible.
693         *
694         * All 64bit Intel CPUs support this MSR. If virtualised, expect
695         * the hypervisor to either emulate the MSR or give us NX.
696         */
697        xor     %eax, %eax
698        cpuid
699        cmp     $X86_VENDOR_INTEL_EBX, %ebx
700        jnz     .Lno_nx
701        cmp     $X86_VENDOR_INTEL_EDX, %edx
702        jnz     .Lno_nx
703        cmp     $X86_VENDOR_INTEL_ECX, %ecx
704        jnz     .Lno_nx
705
706        /* Clear the XD_DISABLE bit */
707        mov     $MSR_IA32_MISC_ENABLE, %ecx
708        rdmsr
709        btr     $2, %edx
710        jnc     .Lno_nx
711        wrmsr
712        orb     $MSR_IA32_MISC_ENABLE_XD_DISABLE >> 32, 4 + sym_esi(trampoline_misc_enable_off)
713
714        /* Check again for NX */
715        mov     $0x80000001, %eax
716        cpuid
717        bt      $cpufeat_bit(X86_FEATURE_NX), %edx
718        jnc     .Lno_nx
719
720.Lgot_nx:
721#ifndef CONFIG_REQUIRE_NX
722        /* Adjust EFER given that NX is present */
723        orb     $EFER_NXE >> 8, 1 + sym_esi(trampoline_efer)
724.Lno_nx:
725#endif
726
727        /* Stash TSC to calculate a good approximation of time-since-boot */
728        rdtsc
729        mov     %eax,     sym_esi(boot_tsc_stamp)
730        mov     %edx, 4 + sym_esi(boot_tsc_stamp)
731
732        /* Relocate pagetables to point at Xen's current location in memory. */
733        mov     $_PAGE_PRESENT, %edx
734        lea     sym_esi(__page_tables_start), %eax
735        lea     sym_esi(__page_tables_end), %edi
736
7371:      test    %edx, (%eax) /* if page present */
738        jz      2f
739        add     %esi, (%eax) /* pte += base */
7402:      add     $8, %eax
741
742        cmp     %edi, %eax
743        jb      1b
744
745        .if !IS_ALIGNED(sym_offs(0), 1 << L2_PAGETABLE_SHIFT)
746        .error "Symbol offset calculation breaks alignment"
747        .endif
748
749        /* Check that the image base is aligned. */
750        lea     sym_esi(_start), %eax
751        test    $(1 << L2_PAGETABLE_SHIFT) - 1, %eax
752        jnz     .Lnot_aligned
753
754        /* Map Xen into the higher mappings using 2M superpages. */
755        lea     _PAGE_PSE + PAGE_HYPERVISOR_RWX + sym_esi(_start), %eax
756        mov     $sym_offs(_start),   %ecx   /* %eax = PTE to write ^      */
757        mov     $sym_offs(_end - 1), %edx
758        shr     $L2_PAGETABLE_SHIFT, %ecx   /* %ecx = First slot to write */
759        shr     $L2_PAGETABLE_SHIFT, %edx   /* %edx = Final slot to write */
760
7611:      mov     %eax, sym_offs(l2_xenmap)(%esi, %ecx, 8)
762        add     $1, %ecx
763        add     $1 << L2_PAGETABLE_SHIFT, %eax
764
765        cmp     %edx, %ecx
766        jbe     1b
767
768        /*
769         * Map Xen into the directmap (needed for early-boot pagetable
770         * handling/walking), and identity map Xen into bootmap (needed for
771         * the transition into long mode), using 2M superpages.
772         */
773        lea     sym_esi(_start), %ecx
774        lea     -1 + sym_esi(_end), %edx
775        lea     _PAGE_PSE + PAGE_HYPERVISOR_RWX(%ecx), %eax /* PTE to write. */
776        shr     $L2_PAGETABLE_SHIFT, %ecx                   /* First slot to write. */
777        shr     $L2_PAGETABLE_SHIFT, %edx                   /* Final slot to write. */
778
7791:      mov     %eax, sym_offs(l2_bootmap)  (%esi, %ecx, 8)
780        mov     %eax, sym_offs(l2_directmap)(%esi, %ecx, 8)
781        add     $1, %ecx
782        add     $1 << L2_PAGETABLE_SHIFT, %eax
783
784        cmp     %edx, %ecx
785        jbe     1b
786
787        /* Map 4x l2_bootmap[] into l3_bootmap[0...3] */
788        lea     __PAGE_HYPERVISOR + sym_esi(l2_bootmap), %eax
789        mov     %eax, 0  + sym_esi(l3_bootmap)
790        add     $PAGE_SIZE, %eax
791        mov     %eax, 8  + sym_esi(l3_bootmap)
792        add     $PAGE_SIZE, %eax
793        mov     %eax, 16 + sym_esi(l3_bootmap)
794        add     $PAGE_SIZE, %eax
795        mov     %eax, 24 + sym_esi(l3_bootmap)
796
797        /* Map l1_bootmap[] into l2_bootmap[0]. */
798        lea     __PAGE_HYPERVISOR + sym_esi(l1_bootmap), %eax
799        mov     %eax, sym_esi(l2_bootmap)
800
801        /* Map the permanent trampoline page into l1_bootmap[]. */
802        mov     sym_esi(trampoline_phys), %ecx
803        lea     __PAGE_HYPERVISOR_RX(%ecx), %edx /* %edx = PTE to write  */
804        shr     $PAGE_SHIFT, %ecx                /* %ecx = Slot to write */
805        mov     %edx, sym_offs(l1_bootmap)(%esi, %ecx, 8)
806
807        /* Apply relocations to bootstrap trampoline. */
808        mov     sym_esi(trampoline_phys), %edx
809        lea     sym_esi(__trampoline_rel_start), %edi
810        lea     sym_esi(__trampoline_rel_stop), %ecx
8111:
812        mov     (%edi), %eax
813        add     %edx, (%edi, %eax)
814        add     $4,%edi
815
816        cmp     %ecx, %edi
817        jb      1b
818
819        /* Patch in the trampoline segment. */
820        shr     $4,%edx
821        lea     sym_esi(__trampoline_seg_start), %edi
822        lea     sym_esi(__trampoline_seg_stop), %ecx
8231:
824        mov     (%edi), %eax
825        mov     %dx, (%edi, %eax)
826        add     $4,%edi
827
828        cmp     %ecx, %edi
829        jb      1b
830
831        /* Do not parse command line on EFI platform here. */
832        cmpb    $0, sym_esi(efi_platform)
833        jnz     1f
834
835        /* Bail if there is no command line to parse. */
836        mov     sym_esi(multiboot_ptr), %ebx
837        testl   $MBI_CMDLINE,MB_flags(%ebx)
838        jz      1f
839
840        lea     sym_esi(early_boot_opts),%eax
841        push    %eax
842        pushl   MB_cmdline(%ebx)
843        call    cmdline_parse_early
844
8451:
846        /* Switch to low-memory stack which lives at the end of trampoline region. */
847        mov     sym_esi(trampoline_phys), %edi
848        lea     TRAMPOLINE_SPACE+TRAMPOLINE_STACK_SPACE(%edi),%esp
849        lea     trampoline_boot_cpu_entry-trampoline_start(%edi),%eax
850        pushl   $BOOT_CS32
851        push    %eax
852
853        /* Copy bootstrap trampoline to low memory, below 1MB. */
854        lea     sym_esi(trampoline_start), %esi
855        mov     $((trampoline_end - trampoline_start) / 4),%ecx
856        rep movsl
857
858        /* Jump into the relocated trampoline. */
859        lret
860
861        /*
862         * cmdline and reloc are written in C, and linked to be 32bit PIC with
863         * entrypoints at 0 and using the stdcall convention.
864         */
865        ALIGN
866cmdline_parse_early:
867        .incbin "cmdline.bin"
868
869        ALIGN
870reloc:
871        .incbin "reloc.bin"
872
873ENTRY(trampoline_start)
874#include "trampoline.S"
875ENTRY(trampoline_end)
876
877#include "x86_64.S"
878