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 ;*   bootsect.asm
     13 ;*    
     14 ;*   bootsect.asm is built as 16-bit binary file in 512 bytes and patched to disk/partition's 
     15 ;*   first section - boot sector. 
     16 ;*
     17 ;*   The startup sequence for DUET disk boot sector is:
     18 ;*
     19 ;*   1, LegacyBios check 0xAA55 signature at boot sectore offset 0x1FE to judget 
     20 ;*      whether disk/partition is bootable.
     21 ;*   2, LegacyBios will load boot sector to 0x7c00 in real mode, pass BPB data and
     22 ;*      hand off control to 0x7c00 code.
     23 ;*   3, boot sector code simply parse FAT format in boot disk and find EfiLdr binary file 
     24 ;*      and EfiVar.bin if exists. For first boot, EfiVar.bin does not exist.
     25 ;*   4, boot sector load the first sector of EfiLdr binary which is start.com to
     26 ;*      0x2000:0x0000 address.
     27 ;*   5, boot sector handoff control to 0x2000:0x0000 for start.com binary.
     28 ;*
     29 ;------------------------------------------------------------------------------
     30 
     31         .model  small
     32         .stack
     33         .486p
     34         .code
     35 
     36 FAT_DIRECTORY_ENTRY_SIZE  EQU     020h
     37 FAT_DIRECTORY_ENTRY_SHIFT EQU     5
     38 BLOCK_SIZE                EQU     0200h
     39 BLOCK_MASK                EQU     01ffh
     40 BLOCK_SHIFT               EQU     9
     41                                                ; "EFILDR_____"
     42 LOADER_FILENAME_PART1     EQU     04c494645h   ; "EFIL"
     43 LOADER_FILENAME_PART2     EQU     020205244h   ; "DR__"
     44 LOADER_FILENAME_PART3     EQU     020202020h   ; "____"
     45 
     46         org 0h
     47 Ia32Jump:
     48   jmp   BootSectorEntryPoint  ; JMP inst                  - 3 bytes
     49   nop
     50 
     51 OemId             db  "INTEL   "    ; OemId               - 8 bytes
     52 ; BPB data below will be fixed by tool
     53 SectorSize        dw  0             ; Sector Size         - 16 bits
     54 SectorsPerCluster db  0             ; Sector Per Cluster  - 8 bits
     55 ReservedSectors   dw  0             ; Reserved Sectors    - 16 bits
     56 NoFats            db  0             ; Number of FATs      - 8 bits
     57 RootEntries       dw  0             ; Root Entries        - 16 bits
     58 Sectors           dw  0             ; Number of Sectors   - 16 bits
     59 Media             db  0             ; Media               - 8 bits  - ignored
     60 SectorsPerFat     dw  0             ; Sectors Per FAT     - 16 bits
     61 SectorsPerTrack   dw  0             ; Sectors Per Track   - 16 bits - ignored
     62 Heads             dw  0             ; Heads               - 16 bits - ignored
     63 HiddenSectors     dd  0             ; Hidden Sectors      - 32 bits - ignored
     64 LargeSectors      dd  0             ; Large Sectors       - 32 bits 
     65 PhysicalDrive     db  0             ; PhysicalDriveNumber - 8 bits  - ignored
     66 CurrentHead       db  0             ; Current Head        - 8 bits
     67 Signature         db  0             ; Signature           - 8 bits  - ignored
     68 Id                db  "    "        ; Id                  - 4 bytes
     69 FatLabel          db  "           " ; Label               - 11 bytes
     70 SystemId          db  "FAT12   "    ; SystemId            - 8 bytes
     71 
     72 BootSectorEntryPoint:
     73         ASSUME  ds:@code
     74         ASSUME  ss:@code
     75 
     76 ; ****************************************************************************
     77 ; Start Print
     78 ; ****************************************************************************
     79   lea  si, cs:[StartString]
     80   call PrintString
     81 
     82 ; ****************************************************************************
     83 ; Print over
     84 ; ****************************************************************************
     85 
     86   mov   ax,cs         ; ax = 0
     87   mov   ss,ax         ; ss = 0
     88   add   ax,1000h
     89   mov   ds,ax
     90 
     91   mov   sp,07c00h     ; sp = 0x7c00
     92   mov   bp,sp         ; bp = 0x7c00
     93 
     94   mov   ah,8                                ; ah = 8 - Get Drive Parameters Function
     95   mov   byte ptr [bp+PhysicalDrive],dl      ; BBS defines that BIOS would pass the booting driver number to the loader through DL
     96   int   13h                                 ; Get Drive Parameters
     97   xor   ax,ax                               ; ax = 0
     98   mov   al,dh                               ; al = dh (number of sides (0 based))
     99   inc   al                                  ; MaxHead = al + 1
    100   push  ax                                  ; 0000:7bfe = MaxHead
    101   mov   al,cl                               ; al = cl (CL = sectors per track)
    102   and   al,03fh                             ; MaxSector = al & 0x3f
    103   push  ax                                  ; 0000:7bfc = MaxSector
    104 
    105   cmp   word ptr [bp+SectorSignature],0aa55h  ; Verify Boot Sector Signature
    106   jne   BadBootSector
    107   mov   cx,word ptr [bp+RootEntries]      ; cx = RootEntries
    108   shl   cx,FAT_DIRECTORY_ENTRY_SHIFT      ; cx = cx * 32 = cx * sizeof(FAT_DIRECTORY_ENTRY) = Size of Root Directory in bytes
    109   mov   bx,cx                             ; bx = size of the Root Directory in bytes
    110   and   bx,BLOCK_MASK                     ; See if it is an even number of sectors long
    111   jne   BadBootSector                     ; If is isn't, then the boot sector is bad.
    112   mov   bx,cx                             ; bx = size of the Root Directory in bytes
    113   shr   bx,BLOCK_SHIFT                    ; bx = size of Root Directory in sectors
    114   mov   al,byte ptr [bp+NoFats]           ; al = NoFats
    115   xor   ah,ah                             ; ah = 0  ==> ax = NoFats
    116   mul   word ptr [bp+SectorsPerFat]       ; ax = NoFats * SectorsPerFat
    117   add   ax,word ptr [bp+ReservedSectors]  ; ax = NoFats * SectorsPerFat + ReservedSectors = RootLBA
    118   push  ds
    119   pop   es
    120   xor   di,di                             ; Store directory in es:di = 1000:0000
    121   call  ReadBlocks                        ; Read entire Root Directory
    122   add   ax,bx                             ; ax = NoFats * SectorsPerFat + ReservedSectors + RootDirSectors = FirstClusterLBA (FirstDataSector)
    123   mov   word ptr [bp],ax                  ; Save FirstClusterLBA (FirstDataSector) for later use
    124 
    125   ; dx - variable storage (initial value is 0)
    126   ; bx - loader (initial value is 0)
    127   xor   dx, dx
    128   xor   bx, bx
    129 
    130 FindEFILDR:
    131   cmp   dword ptr [di],LOADER_FILENAME_PART1         ; Compare to "EFIL"
    132   jne   FindVARSTORE
    133   cmp   dword ptr [di+4],LOADER_FILENAME_PART2
    134   jne   FindVARSTORE
    135   cmp   dword ptr [di+7],LOADER_FILENAME_PART3
    136   jne   FindVARSTORE
    137   mov   bx, word ptr [di+26]              ; bx = Start Cluster for EFILDR  <----------------------------------
    138   test  dx, dx
    139   je    FindNext                          ; Efivar.bin is not loaded
    140   jmp   FoundAll
    141 
    142 FindVARSTORE:
    143   ; if the file is not loader file, see if it's "EFIVAR  BIN"
    144   cmp   dword ptr [di], 056494645h        ; Compare to "EFIV"
    145   jne   FindNext
    146   cmp   dword ptr [di+4], 020205241h      ; Compare to "AR  "
    147   jne   FindNext
    148   cmp   dword ptr [di+7], 04e494220h      ; Compare to " BIN"
    149   jne   FindNext
    150   mov   dx, di                            ; dx = Offset of Start Cluster for Efivar.bin <---------------------
    151   add   dx, 26
    152   test  bx, bx
    153   je    FindNext                          ; Efildr is not loaded
    154   jmp   FoundAll
    155   
    156 FindNext:
    157   ; go to next find
    158   add   di,FAT_DIRECTORY_ENTRY_SIZE       ; Increment di
    159   sub   cx,FAT_DIRECTORY_ENTRY_SIZE       ; Decrement cx
    160   ; TODO: jump to FindVarStore if ...
    161   jne   FindEFILDR
    162   jmp   NotFoundAll
    163 
    164 FoundAll:
    165 FoundEFILDR:                                  ; 0x7cfe
    166   mov     cx,bx                               ; cx = Start Cluster for EFILDR  <----------------------------------
    167   mov     ax,cs                               ; Destination = 2000:0000
    168   add     ax,2000h
    169   mov     es,ax
    170   xor     di,di
    171 ReadFirstClusterOfEFILDR:
    172   mov     ax,cx                               ; ax = StartCluster
    173   sub     ax,2                                ; ax = StartCluster - 2
    174   xor     bh,bh                               
    175   mov     bl,byte ptr [bp+SectorsPerCluster]  ; bx = SectorsPerCluster
    176   push    dx
    177   mul     bx
    178   pop     dx                                  ; ax = (StartCluster - 2) * SectorsPerCluster
    179   add     ax, word ptr [bp]                   ; ax = FirstClusterLBA + (StartCluster-2)*SectorsPerCluster
    180   xor     bh,bh
    181   mov     bl,byte ptr [bp+SectorsPerCluster]  ; bx = Number of Sectors in a cluster
    182   push    es
    183   call    ReadBlocks
    184   pop     ax
    185 JumpIntoFirstSectorOfEFILDR:
    186   mov     word ptr [bp+JumpSegment],ax        ; 0x7d26
    187 JumpFarInstruction:                           ; 0x7d2a
    188   db      0eah
    189 JumpOffset:
    190   dw      0000h
    191 JumpSegment:
    192   dw      2000h
    193 
    194 
    195 PrintString:
    196   mov  ax,0b800h
    197   mov  es,ax
    198   mov  ax, 07c0h
    199   mov  ds, ax
    200   mov  cx, 7
    201   mov  di, 160
    202   rep  movsw
    203   ret
    204 ; ****************************************************************************
    205 ; ReadBlocks - Reads a set of blocks from a block device
    206 ;
    207 ; AX    = Start LBA
    208 ; BX    = Number of Blocks to Read
    209 ; ES:DI = Buffer to store sectors read from disk
    210 ; ****************************************************************************
    211 
    212 ; cx = Blocks
    213 ; bx = NumberOfBlocks
    214 ; si = StartLBA
    215 
    216 ReadBlocks:
    217   pusha
    218   add     eax,dword ptr [bp+LBAOffsetForBootSector]    ; Add LBAOffsetForBootSector to Start LBA
    219   add     eax,dword ptr [bp+HiddenSectors]    ; Add HiddenSectors to Start LBA
    220   mov     esi,eax                             ; esi = Start LBA
    221   mov     cx,bx                               ; cx = Number of blocks to read
    222 ReadCylinderLoop:
    223   mov     bp,07bfch                           ; bp = 0x7bfc
    224   mov     eax,esi                             ; eax = Start LBA
    225   xor     edx,edx                             ; edx = 0
    226   movzx   ebx,word ptr [bp]                   ; bx = MaxSector
    227   div     ebx                                 ; ax = StartLBA / MaxSector
    228   inc     dx                                  ; dx = (StartLBA % MaxSector) + 1
    229   sub     bx,dx                               ; bx = MaxSector - Sector
    230   inc     bx                                  ; bx = MaxSector - Sector + 1
    231   cmp     cx,bx                               ; Compare (Blocks) to (MaxSector - Sector + 1)
    232   jg      LimitTransfer
    233   mov     bx,cx                               ; bx = Blocks
    234 LimitTransfer:
    235   push    cx
    236   mov     cl,dl                               ; cl = (StartLBA % MaxSector) + 1 = Sector
    237   xor     dx,dx                               ; dx = 0
    238   div     word ptr [bp+2]                     ; ax = ax / (MaxHead + 1) = Cylinder  
    239                                               ; dx = ax % (MaxHead + 1) = Head
    240 
    241   push    bx                                  ; Save number of blocks to transfer
    242   mov     dh,dl                               ; dh = Head
    243   mov     bp,07c00h                           ; bp = 0x7c00
    244   mov     dl,byte ptr [bp+PhysicalDrive]      ; dl = Drive Number
    245   mov     ch,al                               ; ch = Cylinder
    246   mov     al,bl                               ; al = Blocks
    247   mov     ah,2                                ; ah = Function 2
    248   mov     bx,di                               ; es:bx = Buffer address
    249   int     013h
    250   jc      DiskError
    251   pop     bx
    252   pop     cx
    253   movzx   ebx,bx
    254   add     esi,ebx                             ; StartLBA = StartLBA + NumberOfBlocks
    255   sub     cx,bx                               ; Blocks = Blocks - NumberOfBlocks
    256   mov     ax,es
    257   shl     bx,(BLOCK_SHIFT-4)
    258   add     ax,bx
    259   mov     es,ax                               ; es:di = es:di + NumberOfBlocks*BLOCK_SIZE
    260   cmp     cx,0
    261   jne     ReadCylinderLoop
    262   popa
    263   ret
    264 
    265 ; ****************************************************************************
    266 ; ERROR Condition:
    267 ; ****************************************************************************
    268 NotFoundAll:                            ; 0x7da6
    269   ; if we found EFILDR, continue
    270   test bx,bx
    271   jne  FoundEFILDR
    272 BadBootSector:
    273 DiskError:
    274   lea  si, cs:[ErrorString]
    275   call PrintString
    276 Halt:
    277   jmp   Halt
    278 
    279 StartString:
    280   db 'B', 0ch, 'S', 0ch, 't', 0ch, 'a', 0ch, 'r', 0ch, 't', 0ch, '!', 0ch
    281 ErrorString:
    282   db 'B', 0ch, 'E', 0ch, 'r', 0ch, 'r', 0ch, 'o', 0ch, 'r', 0ch, '!', 0ch
    283 
    284 ; ****************************************************************************
    285 ; LBA Offset for BootSector, need patched by tool for HD boot.
    286 ; ****************************************************************************
    287 
    288   org 01fah
    289 LBAOffsetForBootSector:
    290   dd        0h
    291 
    292 ; ****************************************************************************
    293 ; Sector Signature
    294 ; ****************************************************************************
    295 
    296   org 01feh
    297 SectorSignature:
    298   dw        0aa55h      ; Boot Sector Signature
    299 
    300   end 
    301   
    302