Home | History | Annotate | Download | only in Ia32
      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     .686p
     26     .model  flat,C
     27 
     28 EXTERNDEF   C   m16Start:BYTE
     29 EXTERNDEF   C   m16Size:WORD
     30 EXTERNDEF   C   mThunk16Attr:WORD
     31 EXTERNDEF   C   m16Gdt:WORD
     32 EXTERNDEF   C   m16GdtrBase:WORD
     33 EXTERNDEF   C   mTransition:WORD
     34 
     35 ;
     36 ; Here is the layout of the real mode stack. _ToUserCode() is responsible for
     37 ; loading all these registers from real mode stack.
     38 ;
     39 IA32_REGS   STRUC   4t
     40 _EDI        DD      ?
     41 _ESI        DD      ?
     42 _EBP        DD      ?
     43 _ESP        DD      ?
     44 _EBX        DD      ?
     45 _EDX        DD      ?
     46 _ECX        DD      ?
     47 _EAX        DD      ?
     48 _DS         DW      ?
     49 _ES         DW      ?
     50 _FS         DW      ?
     51 _GS         DW      ?
     52 _EFLAGS     DD      ?
     53 _EIP        DD      ?
     54 _CS         DW      ?
     55 _SS         DW      ?
     56 IA32_REGS   ENDS
     57 
     58     .const
     59 
     60 ;
     61 ; These are global constant to convey information to C code.
     62 ;
     63 m16Size         DW      InternalAsmThunk16 - m16Start
     64 mThunk16Attr    DW      _ThunkAttr - m16Start
     65 m16Gdt          DW      _NullSegDesc - m16Start
     66 m16GdtrBase     DW      _16GdtrBase - m16Start
     67 mTransition     DW      _EntryPoint - m16Start
     68 
     69     .code
     70 
     71 m16Start    LABEL   BYTE
     72 
     73 SavedGdt    LABEL   FWORD
     74             DW      ?
     75             DD      ?
     76 ;------------------------------------------------------------------------------
     77 ; _BackFromUserCode() takes control in real mode after 'retf' has been executed
     78 ; by user code. It will be shadowed to somewhere in memory below 1MB.
     79 ;------------------------------------------------------------------------------
     80 _BackFromUserCode   PROC
     81     ;
     82     ; The order of saved registers on the stack matches the order they appears
     83     ; in IA32_REGS structure. This facilitates wrapper function to extract them
     84     ; into that structure.
     85     ;
     86     push    ss
     87     push    cs
     88     DB      66h
     89     call    @Base                       ; push eip
     90 @Base:
     91     pushf                               ; pushfd actually
     92     cli                                 ; disable interrupts
     93     push    gs
     94     push    fs
     95     push    es
     96     push    ds
     97     pushaw                              ; pushad actually
     98     DB      66h, 0bah                   ; mov edx, imm32
     99 _ThunkAttr  DD      ?
    100     test    dl, THUNK_ATTRIBUTE_DISABLE_A20_MASK_INT_15
    101     jz      @1
    102     mov     eax, 15cd2401h              ; mov ax, 2401h & int 15h
    103     cli                                 ; disable interrupts
    104     jnc     @2
    105 @1:
    106     test    dl, THUNK_ATTRIBUTE_DISABLE_A20_MASK_KBD_CTRL
    107     jz      @2
    108     in      al, 92h
    109     or      al, 2
    110     out     92h, al                     ; deactivate A20M#
    111 @2:
    112     xor     ax, ax                      ; xor eax, eax
    113     mov     eax, ss                     ; mov ax, ss
    114     DB      67h
    115     lea     bp, [esp + sizeof (IA32_REGS)]
    116     ;
    117     ; esi's in the following 2 instructions are indeed bp in 16-bit code. Fact
    118     ; is "esi" in 32-bit addressing mode has the same encoding of "bp" in 16-
    119     ; bit addressing mode.
    120     ;
    121     mov     word ptr (IA32_REGS ptr [esi - sizeof (IA32_REGS)])._ESP, bp
    122     mov     ebx, (IA32_REGS ptr [esi - sizeof (IA32_REGS)])._EIP
    123     shl     ax, 4                       ; shl eax, 4
    124     add     bp, ax                      ; add ebp, eax
    125     DB      66h, 0b8h                   ; mov eax, imm32
    126 SavedCr4    DD      ?
    127     mov     cr4, eax
    128     DB      66h
    129     lgdt    fword ptr cs:[edi + (SavedGdt - @Base)]
    130     DB      66h, 0b8h                   ; mov eax, imm32
    131 SavedCr0    DD      ?
    132     mov     cr0, eax
    133     DB      0b8h                        ; mov ax, imm16
    134 SavedSs     DW      ?
    135     mov     ss, eax
    136     DB      66h, 0bch                   ; mov esp, imm32
    137 SavedEsp    DD      ?
    138     DB      66h
    139     retf                                ; return to protected mode
    140 _BackFromUserCode   ENDP
    141 
    142 _EntryPoint DD      _ToUserCode - m16Start
    143             DW      8h
    144 _16Idtr     FWORD   (1 SHL 10) - 1
    145 _16Gdtr     LABEL   FWORD
    146             DW      GdtEnd - _NullSegDesc - 1
    147 _16GdtrBase DD      _NullSegDesc
    148 
    149 ;------------------------------------------------------------------------------
    150 ; _ToUserCode() takes control in real mode before passing control to user code.
    151 ; It will be shadowed to somewhere in memory below 1MB.
    152 ;------------------------------------------------------------------------------
    153 _ToUserCode PROC
    154     mov     edx, ss
    155     mov     ss, ecx                     ; set new segment selectors
    156     mov     ds, ecx
    157     mov     es, ecx
    158     mov     fs, ecx
    159     mov     gs, ecx
    160     mov     cr0, eax                    ; real mode starts at next instruction
    161                                         ;  which (per SDM) *must* be a far JMP.
    162     DB      0eah
    163 _RealAddr DW 0,0                       ; filled in by InternalAsmThunk16
    164 
    165     mov     cr4, ebp
    166     mov     ss, esi                     ; set up 16-bit stack segment
    167     xchg    sp, bx                      ; set up 16-bit stack pointer
    168 
    169 ;   mov     bp, [esp + sizeof(IA32_REGS)
    170     DB      67h
    171     mov     ebp, [esp + sizeof(IA32_REGS)] ; BackFromUserCode address from stack
    172 
    173 ;   mov     cs:[bp + (SavedSs - _BackFromUserCode)], dx
    174     mov     cs:[esi + (SavedSs - _BackFromUserCode)], edx
    175 
    176 ;   mov     cs:[bp + (SavedEsp - _BackFromUserCode)], ebx
    177     DB      2eh, 66h, 89h, 9eh
    178     DW      SavedEsp - _BackFromUserCode
    179 
    180 ;   lidt    cs:[bp + (_16Idtr - _BackFromUserCode)]
    181     DB      2eh, 66h, 0fh, 01h, 9eh
    182     DW      _16Idtr - _BackFromUserCode
    183 
    184     popaw                               ; popad actually
    185     pop     ds
    186     pop     es
    187     pop     fs
    188     pop     gs
    189     popf                                ; popfd
    190     DB      66h                         ; Use 32-bit addressing for "retf" below
    191     retf                                ; transfer control to user code
    192 _ToUserCode ENDP
    193 
    194 _NullSegDesc    DQ      0
    195 _16CsDesc       LABEL   QWORD
    196                 DW      -1
    197                 DW      0
    198                 DB      0
    199                 DB      9bh
    200                 DB      8fh             ; 16-bit segment, 4GB limit
    201                 DB      0
    202 _16DsDesc       LABEL   QWORD
    203                 DW      -1
    204                 DW      0
    205                 DB      0
    206                 DB      93h
    207                 DB      8fh             ; 16-bit segment, 4GB limit
    208                 DB      0
    209 GdtEnd          LABEL   QWORD
    210 
    211 ;------------------------------------------------------------------------------
    212 ; IA32_REGISTER_SET *
    213 ; EFIAPI
    214 ; InternalAsmThunk16 (
    215 ;   IN      IA32_REGISTER_SET         *RegisterSet,
    216 ;   IN OUT  VOID                      *Transition
    217 ;   );
    218 ;------------------------------------------------------------------------------
    219 InternalAsmThunk16  PROC    USES    ebp ebx esi edi ds  es  fs  gs
    220     mov     esi, [esp + 36]             ; esi <- RegSet, the 1st parameter
    221     movzx   edx, (IA32_REGS ptr [esi])._SS
    222     mov     edi, (IA32_REGS ptr [esi])._ESP
    223     add     edi, - (sizeof (IA32_REGS) + 4) ; reserve stack space
    224     mov     ebx, edi                    ; ebx <- stack offset
    225     imul    eax, edx, 16                ; eax <- edx * 16
    226     push    sizeof (IA32_REGS) / 4
    227     add     edi, eax                    ; edi <- linear address of 16-bit stack
    228     pop     ecx
    229     rep     movsd                       ; copy RegSet
    230     mov     eax, [esp + 40]             ; eax <- address of transition code
    231     mov     esi, edx                    ; esi <- 16-bit stack segment
    232     lea     edx, [eax + (SavedCr0 - m16Start)]
    233     mov     ecx, eax
    234     and     ecx, 0fh
    235     shl     eax, 12
    236     lea     ecx, [ecx + (_BackFromUserCode - m16Start)]
    237     mov     ax, cx
    238     stosd                               ; [edi] <- return address of user code
    239     add     eax, _RealAddr + 4 - _BackFromUserCode
    240     mov     dword ptr [edx + (_RealAddr - SavedCr0)], eax
    241     sgdt    fword ptr [edx + (SavedGdt - SavedCr0)]
    242     sidt    fword ptr [esp + 36]        ; save IDT stack in argument space
    243     mov     eax, cr0
    244     mov     [edx], eax                  ; save CR0 in SavedCr0
    245     and     eax, 7ffffffeh              ; clear PE, PG bits
    246     mov     ebp, cr4
    247     mov     [edx + (SavedCr4 - SavedCr0)], ebp
    248     and     ebp, NOT 30h                ; clear PAE, PSE bits
    249     push    10h
    250     pop     ecx                         ; ecx <- selector for data segments
    251     lgdt    fword ptr [edx + (_16Gdtr - SavedCr0)]
    252     pushfd                              ; Save df/if indeed
    253     call    fword ptr [edx + (_EntryPoint - SavedCr0)]
    254     popfd
    255     lidt    fword ptr [esp + 36]        ; restore protected mode IDTR
    256     lea     eax, [ebp - sizeof (IA32_REGS)] ; eax <- the address of IA32_REGS
    257     ret
    258 InternalAsmThunk16  ENDP
    259 
    260     END
    261