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