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 ;*    Mbr.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 
     82         xor   ax,ax                               ; AX = 0
     83         mov   ss,ax                               ; SS = 0
     84         add   ax,1000h
     85         mov   ds,ax
     86 
     87         mov   sp,07c00h                           ; SP = 0x7c00
     88         mov   bp,sp                               ; BP = 0x7c00
     89 
     90         mov   ah,8                                ; AH = 8 - Get Drive Parameters Function
     91         mov   byte ptr [bp+PhysicalDrive],dl      ; BBS defines that BIOS would pass the booting driver number to the loader through DL
     92         int   13h                                 ; Get Drive Parameters
     93         xor   ax,ax                               ; AX = 0
     94         mov   al,dh                               ; AL = DH
     95         inc   al                                  ; MaxHead = AL + 1
     96         push  ax                                  ; 0000:7bfe = MaxHead
     97         mov   al,cl                               ; AL = CL
     98         and   al,03fh                             ; MaxSector = AL & 0x3f
     99         push  ax                                  ; 0000:7bfc = MaxSector
    100 
    101 ; ****************************************************************************
    102 ; Read Target DBR from hard disk to 0x0000:0x7C00
    103 ; ****************************************************************************
    104 
    105         xor   ax, ax
    106         mov   al, byte ptr [bp+MbrPartitionIndicator]  ; AX = MbrPartitionIndex
    107         cmp   al, 0ffh                                 ; 0xFF means do legacy MBR boot
    108         jnz   EfiDbr
    109 LegacyMbr:
    110         mov   eax, 00000600h                      ; Assume LegacyMBR is backuped in Sector 6
    111         jmp   StartReadTo7C00                     ; EAX = Header/Sector/Tracker/Zero
    112 
    113 EfiDbr:
    114         cmp   al, 4                               ; MbrPartitionIndex should < 4
    115         jae   BadDbr
    116         shl   ax, 4                               ; AX  = MBREntrySize * Index
    117         add   ax, 1beh                            ; AX  = MBREntryOffset
    118         mov   di, ax                              ; DI  = MBREntryOffset
    119 
    120         ; Here we don't use the C/H/S information provided by Partition table
    121         ;  but calculate C/H/S from LBA ourselves
    122         ;       Ci: Cylinder number
    123         ;       Hi: Header number
    124         ;       Si: Sector number
    125         mov   eax, dword ptr es:[bp + di + 8]     ; Start LBA
    126         mov   edx, eax
    127         shr   edx, 16                             ; DX:AX = Start LBA
    128                                                   ;       = Ci * (H * S) + Hi * S + (Si - 1)
    129 
    130         ; Calculate C/H/S according to LBA
    131         mov   bp, 7bfah
    132         div   word ptr [bp+2]                     ; AX = Hi + H*Ci
    133                                                   ; DX = Si - 1
    134         inc   dx                                  ; DX = Si
    135         push  dx                                  ; 0000:7bfa = Si  <----
    136         xor   dx, dx                              ; DX:AX = Hi + H*Ci
    137         div   word ptr [bp+4]                     ; AX = Ci         <----
    138                                                   ; DX = Hi         <----
    139 
    140 StartReadTo7C00:
    141 
    142         mov   cl, byte ptr [bp]                   ; Si
    143         mov   ch, al                              ; Ci[0-7]
    144         or    cl, ah                              ; Ci[8,9]
    145         mov   bx, 7c00h                           ; ES:BX = 0000:7C00h
    146         mov   ah, 2h                              ; Function 02h
    147         mov   al, 1                               ; 1 Sector
    148         mov   dh, dl                              ; Hi
    149         mov   bp, 0600h
    150         mov   dl, byte ptr [bp + PhysicalDrive]   ; Drive number
    151         int   13h
    152         jc    BadDbr
    153 
    154 
    155 
    156 ; ****************************************************************************
    157 ; Transfer control to BootSector - Jump to 0x0000:0x7C00
    158 ; ****************************************************************************
    159         xor   ax, ax
    160         push  ax                                  ; PUSH 0x0000 - Segment
    161         mov   di, 07c00h
    162         push  di                                  ; PUSH 0x7C00 - Offset
    163         retf                                      ; JMP 0x0000:0x7C00
    164 
    165 ; ****************************************************************************
    166 ; ERROR Condition:
    167 ; ****************************************************************************
    168 
    169 BadDbr:
    170     push ax
    171     mov  ax, 0b800h
    172     mov  es, ax
    173     mov  ax, 060h
    174     mov  ds, ax
    175     lea  si, cs:[ErrorString]
    176     mov  di, 320
    177     pop  ax
    178     call A2C
    179     mov  [si+16], ah
    180     mov  [si+18], al
    181     mov  cx, 10
    182     rep  movsw
    183 Halt:
    184     jmp   Halt
    185 
    186 StartString:
    187     db 'M', 0ch, 'B', 0ch, 'R', 0ch, ' ', 0ch, 'S', 0ch, 't', 0ch, 'a', 0ch, 'r', 0ch, 't', 0ch, '!', 0ch
    188 ErrorString:
    189     db 'M', 0ch, 'B', 0ch, 'R', 0ch, ' ', 0ch, 'E', 0ch, 'r', 0ch, 'r', 0ch, ':', 0ch, '?', 0ch, '?', 0ch
    190 
    191 ; ****************************************************************************
    192 ; A2C - convert Ascii code stored in AH to character stored in AX
    193 ; ****************************************************************************
    194 A2C:
    195     mov  al, ah
    196     shr  ah, 4
    197     and  al, 0Fh
    198     add  ah, '0'
    199     add  al, '0'
    200 
    201     cmp  ah, '9'
    202     jle  @f
    203     add  ah, 7
    204 @@:
    205 
    206     cmp al, '9'
    207     jle @f
    208     add al, 7
    209 @@:
    210     ret
    211 
    212 
    213 ; ****************************************************************************
    214 ; PhysicalDrive - Used to indicate which disk to be boot
    215 ;                 Can be patched by tool
    216 ; ****************************************************************************
    217     org   01B6h
    218 PhysicalDrive         db  80h
    219 
    220 ; ****************************************************************************
    221 ; MbrPartitionIndicator - Used to indicate which MBR partition to be boot
    222 ;                         Can be patched by tool
    223 ;                         OxFF means boot to legacy MBR. (LBA OFFSET 6)
    224 ; ****************************************************************************
    225     org   01B7h
    226 MbrPartitionIndicator db 0
    227 
    228 ; ****************************************************************************
    229 ; Unique MBR signature
    230 ; ****************************************************************************
    231     org   01B8h
    232     db 'DUET'
    233 
    234 ; ****************************************************************************
    235 ; Unknown
    236 ; ****************************************************************************
    237     org   01BCh
    238     dw 0
    239 
    240 ; ****************************************************************************
    241 ; MBR Entry - To be patched
    242 ; ****************************************************************************
    243     org   01BEh
    244     dd 0, 0, 0, 0
    245     org   01CEh
    246     dd 0, 0, 0, 0
    247     org   01DEh
    248     dd 0, 0, 0, 0
    249     org   01EEh
    250     dd 0, 0, 0, 0
    251 
    252 ; ****************************************************************************
    253 ; Sector Signature
    254 ; ****************************************************************************
    255 
    256   org 01FEh
    257 SectorSignature:
    258   dw        0aa55h      ; Boot Sector Signature
    259 
    260   end
    261 
    262