Home | History | Annotate | Download | only in BootSector
      1 ;------------------------------------------------------------------------------
      2 ;*
      3 ;*   Copyright (c) 2006 - 2007, Intel Corporation. All rights reserved.<BR>
      4 ;*   This program and the accompanying materials                          
      5 ;*   are licensed and made available under the terms and conditions of the BSD License         
      6 ;*   which accompanies this distribution.  The full text of the license may be found at        
      7 ;*   http://opensource.org/licenses/bsd-license.php                                            
      8 ;*                                                                                             
      9 ;*   THE PROGRAM IS DISTRIBUTED UNDER THE BSD LICENSE ON AN "AS IS" BASIS,                     
     10 ;*   WITHOUT WARRANTIES OR REPRESENTATIONS OF ANY KIND, EITHER EXPRESS OR IMPLIED.             
     11 ;*   
     12 ;*    gpt.asm
     13 ;*  
     14 ;*   Abstract:
     15 ;*
     16 ;------------------------------------------------------------------------------
     17 
     18     .model  small
     19 ;   .dosseg
     20     .stack
     21     .486p
     22     .code
     23 
     24 BLOCK_SIZE                EQU     0200h
     25 BLOCK_MASK                EQU     01ffh
     26 BLOCK_SHIFT               EQU     9
     27 
     28 ; ****************************************************************************
     29 ; Code loaded by BIOS at 0x0000:0x7C00
     30 ; ****************************************************************************
     31 
     32         org 0h
     33 Start:
     34 
     35 ; ****************************************************************************
     36 ; Start Print
     37 ; ****************************************************************************
     38 
     39     mov  ax,0b800h
     40     mov  es,ax
     41     mov  ax, 07c0h
     42     mov  ds, ax
     43     lea  si, cs:[StartString]
     44     mov  cx, 10
     45     mov  di, 160
     46     rep  movsw 
     47 
     48 ; ****************************************************************************
     49 ; Print over
     50 ; ****************************************************************************
     51 
     52 ; ****************************************************************************
     53 ; Initialize segment registers and copy code at 0x0000:0x7c00 to 0x0000:0x0600
     54 ; ****************************************************************************
     55         xor   ax, ax                    ; AX = 0x0000  
     56         mov   bx, 07c00h                ; BX = 0x7C00
     57         mov   bp, 0600h                 ; BP = 0x0600
     58         mov   si, OFFSET RelocatedStart ; SI = Offset(RelocatedStart)
     59         mov   cx, 0200h                 ; CX = 0x0200
     60         sub   cx, si                    ; CS = 0x0200 - Offset(RelocatedStart)
     61         lea   di, [bp+si]               ; DI = 0x0600 + Offset(RelocatedStart)
     62         lea   si, [bx+si]               ; BX = 0x7C00 + Offset(RelocatedStart)
     63         mov   ss, ax                    ; SS = 0x0000
     64         mov   sp, bx                    ; SP = 0x7C00
     65         mov   es,ax                     ; ES = 0x0000
     66         mov   ds,ax                     ; DS = 0x0000
     67         push  ax                        ; PUSH 0x0000
     68         push  di                        ; PUSH 0x0600 + Offset(RelocatedStart)
     69         cld                             ; Clear the direction flag
     70         rep   movsb                     ; Copy 0x0200 bytes from 0x7C00 to 0x0600
     71         retf                            ; JMP 0x0000:0x0600 + Offset(RelocatedStart)
     72 
     73 ; ****************************************************************************
     74 ; Code relocated to 0x0000:0x0600
     75 ; ****************************************************************************
     76 
     77 RelocatedStart:
     78 ; ****************************************************************************
     79 ; Get Driver Parameters to 0x0000:0x7BFC
     80 ; ****************************************************************************
     81         xor   ax,ax         ; ax = 0
     82         mov   ss,ax         ; ss = 0
     83         add   ax,1000h
     84         mov   ds,ax
     85 
     86         mov   sp,07c00h     ; sp = 0x7c00
     87         mov   bp,sp         ; bp = 0x7c00
     88 
     89         mov   ah,8                                ; ah = 8 - Get Drive Parameters Function
     90         mov   byte ptr [bp+PhysicalDrive],dl      ; BBS defines that BIOS would pass the booting driver number to the loader through DL
     91         int   13h                                 ; Get Drive Parameters
     92         xor   ax,ax                   ; ax = 0
     93         mov   al,dh                   ; al = dh
     94         inc   al                      ; MaxHead = al + 1
     95         push  ax                      ; 0000:7bfe = MaxHead
     96         mov   al,cl                   ; al = cl
     97         and   al,03fh                 ; MaxSector = al & 0x3f
     98         push  ax                      ; 0000:7bfc = MaxSector
     99 
    100 ; ****************************************************************************
    101 ; Read GPT Header from hard disk to 0x0000:0x0800
    102 ; ****************************************************************************
    103         xor     ax, ax
    104         mov     es, ax                            ; Read to 0x0000:0x0800
    105         mov     di, 0800h                         ; Read to 0x0000:0x0800
    106         mov     eax, 1                            ; Read LBA #1
    107         mov     edx, 0                            ; Read LBA #1
    108         mov     bx, 1                             ; Read 1 Block
    109         push    es
    110         call    ReadBlocks
    111         pop     es
    112 
    113 ; ****************************************************************************
    114 ; Read Target GPT Entry from hard disk to 0x0000:0x0A00
    115 ; ****************************************************************************
    116         cmp   dword ptr es:[di], 020494645h       ; Check for "EFI "
    117         jne   BadGpt
    118         cmp   dword ptr es:[di + 4], 054524150h   ; Check for "PART"
    119         jne   BadGpt
    120         cmp   dword ptr es:[di + 8], 000010000h   ; Check Revision - 0x10000
    121         jne   BadGpt
    122 
    123         mov   eax, dword ptr es:[di + 84]         ; EAX = SizeOfPartitionEntry
    124         mul   byte ptr [bp+GptPartitionIndicator] ; EAX = SizeOfPartitionEntry * GptPartitionIndicator
    125         mov   edx, eax                            ; EDX = SizeOfPartitionEntry * GptPartitionIndicator
    126         shr   eax, BLOCK_SHIFT                    ; EAX = (SizeOfPartitionEntry * GptPartitionIndicator) / BLOCK_SIZE
    127         and   edx, BLOCK_MASK                     ; EDX = Targer PartitionEntryLBA Offset
    128                                                   ;     = (SizeOfPartitionEntry * GptPartitionIndicator) % BLOCK_SIZE
    129         push  edx
    130         mov   ecx, dword ptr es:[di + 72]         ; ECX = PartitionEntryLBA (Low)
    131         mov   ebx, dword ptr es:[di + 76]         ; EBX = PartitionEntryLBA (High)
    132         add   eax, ecx                            ; EAX = Target PartitionEntryLBA (Low)
    133                                                   ;     = (PartitionEntryLBA + 
    134                                                   ;        (SizeOfPartitionEntry * GptPartitionIndicator) / BLOCK_SIZE)
    135         adc   edx, ebx                            ; EDX = Target PartitionEntryLBA (High)
    136 
    137         mov   di, 0A00h                           ; Read to 0x0000:0x0A00
    138         mov   bx, 1                               ; Read 1 Block
    139         push  es
    140         call  ReadBlocks
    141         pop   es
    142 
    143 ; ****************************************************************************
    144 ; Read Target DBR from hard disk to 0x0000:0x7C00
    145 ; ****************************************************************************
    146         pop   edx                                 ; EDX = (SizeOfPartitionEntry * GptPartitionIndicator) % BLOCK_SIZE
    147         add   di, dx                              ; DI = Targer PartitionEntryLBA Offset
    148         cmp   dword ptr es:[di], 0C12A7328h       ; Check for EFI System Partition "C12A7328-F81F-11d2-BA4B-00A0C93EC93B"
    149         jne   BadGpt
    150         cmp   dword ptr es:[di + 4], 011d2F81Fh   ; 
    151         jne   BadGpt
    152         cmp   dword ptr es:[di + 8], 0A0004BBAh   ; 
    153         jne   BadGpt
    154         cmp   dword ptr es:[di + 0ch], 03BC93EC9h ; 
    155         jne   BadGpt
    156 
    157         mov   eax, dword ptr es:[di + 32]         ; EAX = StartingLBA (Low)
    158         mov   edx, dword ptr es:[di + 36]         ; EDX = StartingLBA (High)
    159         mov   di, 07C00h                          ; Read to 0x0000:0x7C00
    160         mov   bx, 1                               ; Read 1 Block
    161         call  ReadBlocks
    162 
    163 ; ****************************************************************************
    164 ; Transfer control to BootSector - Jump to 0x0000:0x7C00
    165 ; ****************************************************************************
    166         xor   ax, ax
    167         push  ax                        ; PUSH 0x0000
    168         mov   di, 07c00h
    169         push  di                        ; PUSH 0x7C00
    170         retf                            ; JMP 0x0000:0x7C00
    171 
    172 ; ****************************************************************************
    173 ; ReadBlocks - Reads a set of blocks from a block device
    174 ;
    175 ; EDX:EAX = Start LBA
    176 ; BX      = Number of Blocks to Read (must < 127)
    177 ; ES:DI   = Buffer to store sectors read from disk
    178 ; ****************************************************************************
    179 
    180 ; si = DiskAddressPacket
    181 
    182 ReadBlocks:
    183         pushad
    184         push  ds
    185         xor   cx, cx
    186         mov   ds, cx
    187         mov   bp, 0600h                         ; bp = 0x600
    188         lea   si, [bp + OFFSET AddressPacket]   ; DS:SI = Disk Address Packet
    189         mov   BYTE PTR ds:[si+2],bl             ;    02 = Number Of Block transfered
    190         mov   WORD PTR ds:[si+4],di             ;    04 = Transfer Buffer Offset
    191         mov   WORD PTR ds:[si+6],es             ;    06 = Transfer Buffer Segment
    192         mov   DWORD PTR ds:[si+8],eax           ;    08 = Starting LBA (Low)
    193         mov   DWORD PTR ds:[si+0ch],edx         ;    0C = Starting LBA (High)
    194         mov   ah, 42h                           ; ah = Function 42
    195         mov   dl,byte ptr [bp+PhysicalDrive]    ; dl = Drive Number
    196         int   13h
    197         jc    BadGpt
    198         pop   ds
    199         popad
    200         ret
    201 
    202 ; ****************************************************************************
    203 ; Address Packet used by ReadBlocks
    204 ; ****************************************************************************
    205 AddressPacket:
    206         db    10h                       ; Size of address packet
    207         db    00h                       ; Reserved.  Must be 0
    208         db    01h                       ; Read blocks at a time (To be fixed each times)
    209         db    00h                       ; Reserved.  Must be 0
    210         dw    0000h                     ; Destination Address offset (To be fixed each times)
    211         dw    0000h                     ; Destination Address segment (To be fixed each times)
    212 AddressPacketLba:
    213         dd    0h, 0h                    ; Start LBA (To be fixed each times)
    214 AddressPacketEnd:
    215 
    216 ; ****************************************************************************
    217 ; ERROR Condition:
    218 ; ****************************************************************************
    219 
    220 BadGpt:
    221     mov  ax,0b800h
    222     mov  es,ax
    223     mov  ax, 060h
    224     mov  ds, ax
    225     lea  si, cs:[ErrorString]
    226     mov  cx, 10
    227     mov  di, 320
    228     rep  movsw 
    229 Halt:
    230     jmp   Halt
    231 
    232 StartString:
    233     db 'G', 0ch, 'P', 0ch, 'T', 0ch, ' ', 0ch, 'S', 0ch, 't', 0ch, 'a', 0ch, 'r', 0ch, 't', 0ch, '!', 0ch
    234 ErrorString:
    235     db 'G', 0ch, 'P', 0ch, 'T', 0ch, ' ', 0ch, 'E', 0ch, 'r', 0ch, 'r', 0ch, 'o', 0ch, 'r', 0ch, '!', 0ch
    236 
    237 ; ****************************************************************************
    238 ; PhysicalDrive - Used to indicate which disk to be boot
    239 ;                 Can be patched by tool
    240 ; ****************************************************************************
    241     org   01B6h
    242 PhysicalDrive         db  80h
    243 
    244 ; ****************************************************************************
    245 ; GptPartitionIndicator - Used to indicate which GPT partition to be boot
    246 ;                         Can be patched by tool
    247 ; ****************************************************************************
    248     org   01B7h
    249 GptPartitionIndicator db 0
    250 
    251 ; ****************************************************************************
    252 ; Unique MBR signature
    253 ; ****************************************************************************
    254     org   01B8h
    255     db 'DUET'
    256 
    257 ; ****************************************************************************
    258 ; Unknown
    259 ; ****************************************************************************
    260     org   01BCh
    261     dw 0
    262 
    263 ; ****************************************************************************
    264 ; PMBR Entry - Can be patched by tool
    265 ; ****************************************************************************
    266     org   01BEh
    267     db 0          ; Boot Indicator
    268     db 0ffh       ; Start Header
    269     db 0ffh       ; Start Sector
    270     db 0ffh       ; Start Track
    271     db 0eeh       ; OS Type
    272     db 0ffh       ; End Header
    273     db 0ffh       ; End Sector
    274     db 0ffh       ; End Track
    275     dd 1          ; Starting LBA
    276     dd 0FFFFFFFFh ; End LBA
    277 
    278     org   01CEh
    279     dd 0, 0, 0, 0
    280     org   01DEh
    281     dd 0, 0, 0, 0
    282     org   01EEh
    283     dd 0, 0, 0, 0
    284 
    285 ; ****************************************************************************
    286 ; Sector Signature
    287 ; ****************************************************************************
    288 
    289   org 01FEh
    290 SectorSignature:
    291   dw        0aa55h      ; Boot Sector Signature
    292 
    293   end 
    294   
    295