Home | History | Annotate | Download | only in Ia32
      1 ;------------------------------------------------------------------------------ ;
      2 ; Copyright (c) 2009 - 2016, Intel Corporation. All rights reserved.<BR>
      3 ; This program and the accompanying materials
      4 ; are licensed and made available under the terms and conditions of the BSD License
      5 ; which accompanies this distribution.  The full text of the license may be found at
      6 ; http://opensource.org/licenses/bsd-license.php.
      7 ;
      8 ; THE PROGRAM IS DISTRIBUTED UNDER THE BSD LICENSE ON AN "AS IS" BASIS,
      9 ; WITHOUT WARRANTIES OR REPRESENTATIONS OF ANY KIND, EITHER EXPRESS OR IMPLIED.
     10 ;
     11 ; Module Name:
     12 ;
     13 ;   SmiEntry.asm
     14 ;
     15 ; Abstract:
     16 ;
     17 ;   Code template of the SMI handler for a particular processor
     18 ;
     19 ;-------------------------------------------------------------------------------
     20 
     21     .686p
     22     .model  flat,C
     23     .xmm
     24 
     25 MSR_IA32_MISC_ENABLE  EQU     1A0h
     26 MSR_EFER      EQU     0c0000080h
     27 MSR_EFER_XD   EQU     0800h
     28 
     29 ;
     30 ; Constants relating to TXT_PROCESSOR_SMM_DESCRIPTOR
     31 ;
     32 DSC_OFFSET    EQU     0fb00h
     33 DSC_GDTPTR    EQU     48h
     34 DSC_GDTSIZ    EQU     50h
     35 DSC_CS        EQU     14h
     36 DSC_DS        EQU     16h
     37 DSC_SS        EQU     18h
     38 DSC_OTHERSEG  EQU     1Ah
     39 
     40 PROTECT_MODE_CS EQU   08h
     41 PROTECT_MODE_DS EQU   20h
     42 TSS_SEGMENT     EQU   40h
     43 
     44 SmiRendezvous      PROTO   C
     45 CpuSmmDebugEntry   PROTO   C
     46 CpuSmmDebugExit    PROTO   C
     47 
     48 EXTERNDEF   gcStmSmiHandlerTemplate:BYTE
     49 EXTERNDEF   gcStmSmiHandlerSize:WORD
     50 EXTERNDEF   gcStmSmiHandlerOffset:WORD
     51 EXTERNDEF   gStmSmiCr3:DWORD
     52 EXTERNDEF   gStmSmiStack:DWORD
     53 EXTERNDEF   gStmSmbase:DWORD
     54 EXTERNDEF   gStmXdSupported:BYTE
     55 EXTERNDEF   FeaturePcdGet (PcdCpuSmmStackGuard):BYTE
     56 EXTERNDEF   gStmSmiHandlerIdtr:FWORD
     57 
     58     .code
     59 
     60 gcStmSmiHandlerTemplate    LABEL   BYTE
     61 
     62 _StmSmiEntryPoint:
     63     DB      0bbh                        ; mov bx, imm16
     64     DW      offset _StmGdtDesc - _StmSmiEntryPoint + 8000h
     65     DB      2eh, 0a1h                   ; mov ax, cs:[offset16]
     66     DW      DSC_OFFSET + DSC_GDTSIZ
     67     dec     eax
     68     mov     cs:[edi], eax               ; mov cs:[bx], ax
     69     DB      66h, 2eh, 0a1h              ; mov eax, cs:[offset16]
     70     DW      DSC_OFFSET + DSC_GDTPTR
     71     mov     cs:[edi + 2], ax            ; mov cs:[bx + 2], eax
     72     mov     bp, ax                      ; ebp = GDT base
     73     DB      66h
     74     lgdt    fword ptr cs:[edi]          ; lgdt fword ptr cs:[bx]
     75 ; Patch ProtectedMode Segment
     76     DB      0b8h                        ; mov ax, imm16
     77     DW      PROTECT_MODE_CS             ; set AX for segment directly
     78     mov     cs:[edi - 2], eax           ; mov cs:[bx - 2], ax
     79 ; Patch ProtectedMode entry
     80     DB      66h, 0bfh                   ; mov edi, SMBASE
     81 gStmSmbase    DD    ?
     82     DB      67h
     83     lea     ax, [edi + (@32bit - _StmSmiEntryPoint) + 8000h]
     84     mov     cs:[edi - 6], ax            ; mov cs:[bx - 6], eax
     85     mov     ebx, cr0
     86     DB      66h
     87     and     ebx, 9ffafff3h
     88     DB      66h
     89     or      ebx, 23h
     90     mov     cr0, ebx
     91     DB      66h, 0eah
     92     DD      ?
     93     DW      ?
     94 _StmGdtDesc    FWORD   ?
     95 
     96 @32bit:
     97     mov     ax, PROTECT_MODE_DS
     98     mov     ds, ax
     99     mov     es, ax
    100     mov     fs, ax
    101     mov     gs, ax
    102     mov     ss, ax
    103     DB      0bch                   ; mov esp, imm32
    104 gStmSmiStack   DD      ?
    105     mov     eax, offset gStmSmiHandlerIdtr
    106     lidt    fword ptr [eax]
    107     jmp     ProtFlatMode
    108 
    109 ProtFlatMode:
    110     DB      0b8h                        ; mov eax, imm32
    111 gStmSmiCr3     DD      ?
    112     mov     cr3, eax
    113 ;
    114 ; Need to test for CR4 specific bit support
    115 ;
    116     mov     eax, 1
    117     cpuid                               ; use CPUID to determine if specific CR4 bits are supported
    118     xor     eax, eax                    ; Clear EAX
    119     test    edx, BIT2                   ; Check for DE capabilities
    120     jz      @f
    121     or      eax, BIT3
    122 @@:
    123     test    edx, BIT6                   ; Check for PAE capabilities
    124     jz      @f
    125     or      eax, BIT5
    126 @@:
    127     test    edx, BIT7                   ; Check for MCE capabilities
    128     jz      @f
    129     or      eax, BIT6
    130 @@:
    131     test    edx, BIT24                  ; Check for FXSR capabilities
    132     jz      @f
    133     or      eax, BIT9
    134 @@:
    135     test    edx, BIT25                  ; Check for SSE capabilities
    136     jz      @f
    137     or      eax, BIT10
    138 @@:                                     ; as cr4.PGE is not set here, refresh cr3
    139     mov     cr4, eax                    ; in PreModifyMtrrs() to flush TLB.
    140 
    141     cmp     FeaturePcdGet (PcdCpuSmmStackGuard), 0
    142     jz      @F
    143 ; Load TSS
    144     mov     byte ptr [ebp + TSS_SEGMENT + 5], 89h ; clear busy flag
    145     mov     eax, TSS_SEGMENT
    146     ltr     ax
    147 @@:
    148 
    149 ; enable NXE if supported
    150     DB      0b0h                        ; mov al, imm8
    151 gStmXdSupported     DB      1
    152     cmp     al, 0
    153     jz      @SkipXd
    154 ;
    155 ; Check XD disable bit
    156 ;
    157     mov     ecx, MSR_IA32_MISC_ENABLE
    158     rdmsr
    159     push    edx                        ; save MSR_IA32_MISC_ENABLE[63-32]
    160     test    edx, BIT2                  ; MSR_IA32_MISC_ENABLE[34]
    161     jz      @f
    162     and     dx, 0FFFBh                 ; clear XD Disable bit if it is set
    163     wrmsr
    164 @@:
    165     mov     ecx, MSR_EFER
    166     rdmsr
    167     or      ax, MSR_EFER_XD             ; enable NXE
    168     wrmsr
    169     jmp     @XdDone
    170 @SkipXd:
    171     sub     esp, 4
    172 @XdDone:
    173 
    174     mov     ebx, cr0
    175     or      ebx, 080010023h             ; enable paging + WP + NE + MP + PE
    176     mov     cr0, ebx
    177     lea     ebx, [edi + DSC_OFFSET]
    178     mov     ax, [ebx + DSC_DS]
    179     mov     ds, eax
    180     mov     ax, [ebx + DSC_OTHERSEG]
    181     mov     es, eax
    182     mov     fs, eax
    183     mov     gs, eax
    184     mov     ax, [ebx + DSC_SS]
    185     mov     ss, eax
    186 
    187 CommonHandler:
    188     mov     ebx, [esp + 4]                  ; CPU Index
    189     push    ebx
    190     mov     eax, CpuSmmDebugEntry
    191     call    eax
    192     add     esp, 4
    193 
    194     push    ebx
    195     mov     eax, SmiRendezvous
    196     call    eax
    197     add     esp, 4
    198 
    199     push    ebx
    200     mov     eax, CpuSmmDebugExit
    201     call    eax
    202     add     esp, 4
    203 
    204     mov     eax, gStmXdSupported
    205     mov     al, [eax]
    206     cmp     al, 0
    207     jz      @f
    208     pop     edx                       ; get saved MSR_IA32_MISC_ENABLE[63-32]
    209     test    edx, BIT2
    210     jz      @f
    211     mov     ecx, MSR_IA32_MISC_ENABLE
    212     rdmsr
    213     or      dx, BIT2                  ; set XD Disable bit if it was set before entering into SMM
    214     wrmsr
    215 
    216 @@:
    217     rsm
    218 
    219 _StmSmiHandler:
    220 ;
    221 ; Check XD disable bit
    222 ;
    223     xor     esi, esi
    224     mov     eax, gStmXdSupported
    225     mov     al, [eax]
    226     cmp     al, 0
    227     jz      @StmXdDone
    228     mov     ecx, MSR_IA32_MISC_ENABLE
    229     rdmsr
    230     mov     esi, edx                   ; save MSR_IA32_MISC_ENABLE[63-32]
    231     test    edx, BIT2                  ; MSR_IA32_MISC_ENABLE[34]
    232     jz      @f
    233     and     dx, 0FFFBh                 ; clear XD Disable bit if it is set
    234     wrmsr
    235 @@:
    236     mov     ecx, MSR_EFER
    237     rdmsr
    238     or      ax, MSR_EFER_XD             ; enable NXE
    239     wrmsr
    240 @StmXdDone:
    241     push    esi
    242 
    243     ; below step is needed, because STM does not run above code.
    244     ; we have to run below code to set IDT/CR0/CR4
    245     mov     eax, offset gStmSmiHandlerIdtr
    246     lidt    fword ptr [eax]
    247 
    248 
    249     mov     eax, cr0
    250     or      eax, 80010023h              ; enable paging + WP + NE + MP + PE
    251     mov     cr0, eax
    252 ;
    253 ; Need to test for CR4 specific bit support
    254 ;
    255     mov     eax, 1
    256     cpuid                               ; use CPUID to determine if specific CR4 bits are supported
    257     mov     eax, cr4                    ; init EAX
    258     test    edx, BIT2                   ; Check for DE capabilities
    259     jz      @f
    260     or      eax, BIT3
    261 @@:
    262     test    edx, BIT6                   ; Check for PAE capabilities
    263     jz      @f
    264     or      eax, BIT5
    265 @@:
    266     test    edx, BIT7                   ; Check for MCE capabilities
    267     jz      @f
    268     or      eax, BIT6
    269 @@:
    270     test    edx, BIT24                  ; Check for FXSR capabilities
    271     jz      @f
    272     or      eax, BIT9
    273 @@:
    274     test    edx, BIT25                  ; Check for SSE capabilities
    275     jz      @f
    276     or      eax, BIT10
    277 @@:                                     ; as cr4.PGE is not set here, refresh cr3
    278     mov     cr4, eax                    ; in PreModifyMtrrs() to flush TLB.
    279     ; STM init finish
    280     jmp     CommonHandler
    281 
    282 gcStmSmiHandlerSize    DW      $ - _StmSmiEntryPoint
    283 gcStmSmiHandlerOffset  DW      _StmSmiHandler - _StmSmiEntryPoint
    284 
    285     END
    286