Home | History | Annotate | Download | only in X64
      1 
      2 #include "BaseLibInternals.h"
      3 
      4 ;------------------------------------------------------------------------------
      5 ;
      6 ; Copyright (c) 2006 - 2013, Intel Corporation. All rights reserved.<BR>
      7 ; This program and the accompanying materials
      8 ; are licensed and made available under the terms and conditions of the BSD License
      9 ; which accompanies this distribution.  The full text of the license may be found at
     10 ; http://opensource.org/licenses/bsd-license.php.
     11 ;
     12 ; THE PROGRAM IS DISTRIBUTED UNDER THE BSD LICENSE ON AN "AS IS" BASIS,
     13 ; WITHOUT WARRANTIES OR REPRESENTATIONS OF ANY KIND, EITHER EXPRESS OR IMPLIED.
     14 ;
     15 ; Module Name:
     16 ;
     17 ;   Thunk.asm
     18 ;
     19 ; Abstract:
     20 ;
     21 ;   Real mode thunk
     22 ;
     23 ;------------------------------------------------------------------------------
     24 
     25 global ASM_PFX(m16Size)
     26 global ASM_PFX(mThunk16Attr)
     27 global ASM_PFX(m16Gdt)
     28 global ASM_PFX(m16GdtrBase)
     29 global ASM_PFX(mTransition)
     30 global ASM_PFX(m16Start)
     31 
     32 struc IA32_REGS
     33 
     34   ._EDI:       resd      1
     35   ._ESI:       resd      1
     36   ._EBP:       resd      1
     37   ._ESP:       resd      1
     38   ._EBX:       resd      1
     39   ._EDX:       resd      1
     40   ._ECX:       resd      1
     41   ._EAX:       resd      1
     42   ._DS:        resw      1
     43   ._ES:        resw      1
     44   ._FS:        resw      1
     45   ._GS:        resw      1
     46   ._EFLAGS:    resq      1
     47   ._EIP:       resd      1
     48   ._CS:        resw      1
     49   ._SS:        resw      1
     50   .size:
     51 
     52 endstruc
     53 
     54 SECTION .data
     55 
     56 ;
     57 ; These are global constant to convey information to C code.
     58 ;
     59 ASM_PFX(m16Size)         DW      ASM_PFX(InternalAsmThunk16) - ASM_PFX(m16Start)
     60 ASM_PFX(mThunk16Attr)    DW      _BackFromUserCode.ThunkAttrEnd - 4 - ASM_PFX(m16Start)
     61 ASM_PFX(m16Gdt)          DW      _NullSeg - ASM_PFX(m16Start)
     62 ASM_PFX(m16GdtrBase)     DW      _16GdtrBase - ASM_PFX(m16Start)
     63 ASM_PFX(mTransition)     DW      _EntryPoint - ASM_PFX(m16Start)
     64 
     65 SECTION .text
     66 
     67 ASM_PFX(m16Start):
     68 
     69 SavedGdt:
     70             dw  0
     71             dq  0
     72 
     73 ;------------------------------------------------------------------------------
     74 ; _BackFromUserCode() takes control in real mode after 'retf' has been executed
     75 ; by user code. It will be shadowed to somewhere in memory below 1MB.
     76 ;------------------------------------------------------------------------------
     77 _BackFromUserCode:
     78     ;
     79     ; The order of saved registers on the stack matches the order they appears
     80     ; in IA32_REGS structure. This facilitates wrapper function to extract them
     81     ; into that structure.
     82     ;
     83 BITS    16
     84     push    ss
     85     push    cs
     86     ;
     87     ; Note: We can't use o32 on the next instruction because of a bug
     88     ; in NASM 2.09.04 through 2.10rc1.
     89     ;
     90     call    dword .Base                 ; push eip
     91 .Base:
     92     push    dword 0                     ; reserved high order 32 bits of EFlags
     93     pushfd
     94     cli                                 ; disable interrupts
     95     push    gs
     96     push    fs
     97     push    es
     98     push    ds
     99     pushad
    100     mov     edx, strict dword 0
    101 .ThunkAttrEnd:
    102     test    dl, THUNK_ATTRIBUTE_DISABLE_A20_MASK_INT_15
    103     jz      .1
    104     mov     ax, 2401h
    105     int     15h
    106     cli                                 ; disable interrupts
    107     jnc     .2
    108 .1:
    109     test    dl, THUNK_ATTRIBUTE_DISABLE_A20_MASK_KBD_CTRL
    110     jz      .2
    111     in      al, 92h
    112     or      al, 2
    113     out     92h, al                     ; deactivate A20M#
    114 .2:
    115     xor     eax, eax
    116     mov     ax, ss
    117     lea     ebp, [esp + IA32_REGS.size]
    118     mov     [bp - IA32_REGS.size + IA32_REGS._ESP], ebp
    119     mov     ebx, [bp - IA32_REGS.size + IA32_REGS._EIP]
    120     shl     eax, 4                      ; shl eax, 4
    121     add     ebp, eax                    ; add ebp, eax
    122     mov     eax, cs
    123     shl     eax, 4
    124     lea     eax, [eax + ebx + (.X64JmpEnd - .Base)]
    125     mov     [cs:bx + (.X64JmpEnd - 6 - .Base)], eax
    126     mov     eax, strict dword 0
    127 .SavedCr4End:
    128     mov     cr4, eax
    129 o32 lgdt [cs:bx + (SavedGdt - .Base)]
    130     mov     ecx, 0c0000080h
    131     rdmsr
    132     or      ah, 1
    133     wrmsr
    134     mov     eax, strict dword 0
    135 .SavedCr0End:
    136     mov     cr0, eax
    137     jmp     0:strict dword 0
    138 .X64JmpEnd:
    139 BITS    64
    140     nop
    141     mov rsp, strict qword 0
    142 .SavedSpEnd:
    143     nop
    144     ret
    145 
    146 _EntryPoint:
    147         DD      _ToUserCode - ASM_PFX(m16Start)
    148         DW      CODE16
    149 _16Gdtr:
    150         DW      GDT_SIZE - 1
    151 _16GdtrBase:
    152         DQ      0
    153 _16Idtr:
    154         DW      (1 << 10) - 1
    155         DD      0
    156 
    157 ;------------------------------------------------------------------------------
    158 ; _ToUserCode() takes control in real mode before passing control to user code.
    159 ; It will be shadowed to somewhere in memory below 1MB.
    160 ;------------------------------------------------------------------------------
    161 _ToUserCode:
    162 BITS    16
    163     mov     ss, dx                      ; set new segment selectors
    164     mov     ds, dx
    165     mov     es, dx
    166     mov     fs, dx
    167     mov     gs, dx
    168     mov     ecx, 0c0000080h
    169     mov     cr0, eax                    ; real mode starts at next instruction
    170     rdmsr
    171     and     ah, ~1
    172     wrmsr
    173     mov     cr4, ebp
    174     mov     ss, si                      ; set up 16-bit stack segment
    175     mov     esp, ebx                    ; set up 16-bit stack pointer
    176     call    dword .Base                 ; push eip
    177 .Base:
    178     pop     ebp                         ; ebp <- address of .Base
    179     push    word [dword esp + IA32_REGS.size + 2]
    180     lea     ax, [bp + (.RealMode - .Base)]
    181     push    ax
    182     retf                                ; execution begins at next instruction
    183 .RealMode:
    184 
    185 o32 lidt    [cs:bp + (_16Idtr - .Base)]
    186 
    187     popad
    188     pop     ds
    189     pop     es
    190     pop     fs
    191     pop     gs
    192     popfd
    193     lea     esp, [esp + 4]        ; skip high order 32 bits of EFlags
    194 
    195 o32 retf                                ; transfer control to user code
    196 
    197 ALIGN   8
    198 
    199 CODE16  equ _16Code - $
    200 DATA16  equ _16Data - $
    201 DATA32  equ _32Data - $
    202 
    203 _NullSeg    DQ      0
    204 _16Code:
    205             DW      -1
    206             DW      0
    207             DB      0
    208             DB      9bh
    209             DB      8fh                 ; 16-bit segment, 4GB limit
    210             DB      0
    211 _16Data:
    212             DW      -1
    213             DW      0
    214             DB      0
    215             DB      93h
    216             DB      8fh                 ; 16-bit segment, 4GB limit
    217             DB      0
    218 _32Data:
    219             DW      -1
    220             DW      0
    221             DB      0
    222             DB      93h
    223             DB      0cfh                ; 16-bit segment, 4GB limit
    224             DB      0
    225 
    226 GDT_SIZE equ $ - _NullSeg
    227 
    228 ;------------------------------------------------------------------------------
    229 ; IA32_REGISTER_SET *
    230 ; EFIAPI
    231 ; InternalAsmThunk16 (
    232 ;   IN      IA32_REGISTER_SET         *RegisterSet,
    233 ;   IN OUT  VOID                      *Transition
    234 ;   );
    235 ;------------------------------------------------------------------------------
    236 global ASM_PFX(InternalAsmThunk16)
    237 ASM_PFX(InternalAsmThunk16):
    238 BITS    64
    239     push    rbp
    240     push    rbx
    241     push    rsi
    242     push    rdi
    243     
    244     mov     ebx, ds
    245     push    rbx          ; Save ds segment register on the stack
    246     mov     ebx, es
    247     push    rbx          ; Save es segment register on the stack
    248     mov     ebx, ss
    249     push    rbx          ; Save ss segment register on the stack
    250     
    251     push    fs
    252     push    gs
    253     mov     rsi, rcx
    254     movzx   r8d, word [rsi + IA32_REGS._SS]
    255     mov     edi, [rsi + IA32_REGS._ESP]
    256     lea     rdi, [edi - (IA32_REGS.size + 4)]
    257     imul    eax, r8d, 16                ; eax <- r8d(stack segment) * 16
    258     mov     ebx, edi                    ; ebx <- stack for 16-bit code
    259     push    IA32_REGS.size / 4
    260     add     edi, eax                    ; edi <- linear address of 16-bit stack
    261     pop     rcx
    262     rep     movsd                       ; copy RegSet
    263     lea     ecx, [rdx + (_BackFromUserCode.SavedCr4End - ASM_PFX(m16Start))]
    264     mov     eax, edx                    ; eax <- transition code address
    265     and     edx, 0fh
    266     shl     eax, 12                     ; segment address in high order 16 bits
    267     lea     ax, [rdx + (_BackFromUserCode - ASM_PFX(m16Start))]  ; offset address
    268     stosd                               ; [edi] <- return address of user code
    269   
    270     sgdt    [rsp + 60h]       ; save GDT stack in argument space
    271     movzx   r10, word [rsp + 60h]   ; r10 <- GDT limit 
    272     lea     r11, [rcx + (ASM_PFX(InternalAsmThunk16) - _BackFromUserCode.SavedCr4End) + 0xf]
    273     and     r11, ~0xf            ; r11 <- 16-byte aligned shadowed GDT table in real mode buffer
    274     
    275     mov     [rcx + (SavedGdt - _BackFromUserCode.SavedCr4End)], r10w      ; save the limit of shadowed GDT table
    276     mov     [rcx + (SavedGdt - _BackFromUserCode.SavedCr4End) + 2], r11  ; save the base address of shadowed GDT table
    277     
    278     mov     rsi, [rsp + 62h]  ; rsi <- the original GDT base address
    279     xchg    rcx, r10                    ; save rcx to r10 and initialize rcx to be the limit of GDT table
    280     inc     rcx                         ; rcx <- the size of memory to copy
    281     xchg    rdi, r11                    ; save rdi to r11 and initialize rdi to the base address of shadowed GDT table
    282     rep     movsb                       ; perform memory copy to shadow GDT table
    283     mov     rcx, r10                    ; restore the orignal rcx before memory copy
    284     mov     rdi, r11                    ; restore the original rdi before memory copy
    285     
    286     sidt    [rsp + 50h]       ; save IDT stack in argument space
    287     mov     rax, cr0
    288     mov     [rcx + (_BackFromUserCode.SavedCr0End - 4 - _BackFromUserCode.SavedCr4End)], eax
    289     and     eax, 7ffffffeh              ; clear PE, PG bits
    290     mov     rbp, cr4
    291     mov     [rcx - 4], ebp              ; save CR4 in _BackFromUserCode.SavedCr4End - 4
    292     and     ebp, ~30h                ; clear PAE, PSE bits
    293     mov     esi, r8d                    ; esi <- 16-bit stack segment
    294     push    DATA32
    295     pop     rdx                         ; rdx <- 32-bit data segment selector
    296     lgdt    [rcx + (_16Gdtr - _BackFromUserCode.SavedCr4End)]
    297     mov     ss, edx
    298     pushfq
    299     lea     edx, [rdx + DATA16 - DATA32]
    300     lea     r8, [REL .RetFromRealMode]
    301     push    r8
    302     mov     r8d, cs
    303     mov     [rcx + (_BackFromUserCode.X64JmpEnd - 2 - _BackFromUserCode.SavedCr4End)], r8w
    304     mov     [rcx + (_BackFromUserCode.SavedSpEnd - 8 - _BackFromUserCode.SavedCr4End)], rsp
    305     jmp     dword far [rcx + (_EntryPoint - _BackFromUserCode.SavedCr4End)]
    306 .RetFromRealMode:
    307     popfq
    308     lgdt    [rsp + 60h]       ; restore protected mode GDTR
    309     lidt    [rsp + 50h]       ; restore protected mode IDTR
    310     lea     eax, [rbp - IA32_REGS.size]
    311     pop     gs
    312     pop     fs
    313     pop     rbx
    314     mov     ss, ebx
    315     pop     rbx
    316     mov     es, ebx
    317     pop     rbx
    318     mov     ds, ebx
    319 
    320     pop     rdi
    321     pop     rsi
    322     pop     rbx
    323     pop     rbp
    324 
    325     ret
    326