Home | History | Annotate | Download | only in BootSector
      1 #------------------------------------------------------------------------------
      2 #*
      3 #*   Copyright (c) 2006 - 2012, 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     .code16
     19 
     20 .equ                      BLOCK_SIZE, 0x0200
     21 .equ                      BLOCK_MASK, 0x01ff
     22 .equ                      BLOCK_SHIFT, 9
     23 
     24 # ****************************************************************************
     25 # Code loaded by BIOS at 0x0000:0x7C00
     26 # ****************************************************************************
     27 
     28 .org 0x0
     29 
     30 .global _start
     31 _start:
     32 
     33 # ****************************************************************************
     34 # Start Print
     35 # ****************************************************************************
     36 
     37         movw $0xb800, %ax
     38         movw %ax, %es
     39         movw $0x7c0, %ax
     40         movw %ax, %ds
     41         leaw %cs:StartString, %si
     42         movw $10, %cx
     43         movw $160, %di
     44         rep
     45         movsw
     46 
     47 # ****************************************************************************
     48 # Print over
     49 # ****************************************************************************
     50 
     51 # ****************************************************************************
     52 # Initialize segment registers and copy code at 0x0000:0x7c00 to 0x0000:0x0600
     53 # ****************************************************************************
     54         xorw  %ax, %ax                            # AX = 0x0000
     55         movw  $0x7c00, %bx                        # BX = 0x7C00
     56         movw  $0x600, %bp                         # BP = 0x0600
     57         movw  $RelocatedStart, %si                # SI = Offset(RelocatedStart)
     58         movw  $0x200, %cx                         # CX = 0x0200
     59         subw  %si, %cx                            # CS = 0x0200 - Offset(RelocatedStart)
     60         leaw  (%bp,%si,), %di                     # DI = 0x0600 + Offset(RelocatedStart)
     61         leaw  (%bx,%si,), %si                     # BX = 0x7C00 + Offset(RelocatedStart)
     62         movw  %ax, %ss                            # SS = 0x0000
     63         movw  %bx, %sp                            # SP = 0x7C00
     64         movw  %ax, %es                            # ES = 0x0000
     65         movw  %ax, %ds                            # DS = 0x0000
     66         pushw %ax                                 # PUSH 0x0000
     67         pushw %di                                 # PUSH 0x0600 + Offset(RelocatedStart)
     68         cld                                       # Clear the direction flag
     69         rep
     70         movsb                                     # Copy 0x0200 bytes from 0x7C00 to 0x0600
     71         retl                                      # 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         xorw  %ax, %ax                            # AX = 0
     83         movw  %ax, %ss                            # SS = 0
     84         addw  $0x1000, %ax
     85         movw  %ax, %ds
     86 
     87         movw  $0x7c00, %sp                        # SP = 0x7c00
     88         movw  %sp, %bp                            # BP = 0x7c00
     89 
     90         movb  $8, %ah                             # AH = 8 - Get Drive Parameters Function
     91         movb  %dl, PhysicalDrive(%bp)             # BBS defines that BIOS would pass the booting driver number to the loader through DL
     92         int   $0x13                               # Get Drive Parameters
     93         xorw  %ax, %ax                            # AX = 0
     94         movb  %dh, %al                            # AL = DH
     95         incb  %al                                 # MaxHead = AL + 1
     96         pushw %ax                                 # 0000:7bfe = MaxHead
     97         movb  %cl, %al                            # AL = CL
     98         andb  $0x3f, %al                          # MaxSector = AL & 0x3f
     99         pushw %ax                                 # 0000:7bfc = MaxSector
    100 
    101 # ****************************************************************************
    102 # Read Target DBR from hard disk to 0x0000:0x7C00
    103 # ****************************************************************************
    104 
    105         xorw  %ax, %ax
    106         movb  MbrPartitionIndicator(%bp), %al          # AX = MbrPartitionIndex
    107         cmpb  $0xff, %al                               # 0xFF means do legacy MBR boot
    108         jnz   EfiDbr
    109 LegacyMbr:
    110         movl  $0x0000600, %eax                    # Assume LegacyMBR is backuped in Sector 6
    111         jmp   StartReadTo7C00                     # EAX = Header/Sector/Tracker/Zero
    112 
    113 EfiDbr:
    114         cmpb  $4, %al                             # MbrPartitionIndex should < 4
    115         jae   BadDbr
    116         shlw  $4, %ax                             # AX  = MBREntrySize * Index
    117         addw  $0x1be, %ax                         # AX  = MBREntryOffset
    118         movw  %ax, %di                            # 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         movl  %es:8(%bp,%di,), %eax               # Start LBA
    126         movl  %eax, %edx
    127         shrl  $16, %edx                           # DX:AX = Start LBA
    128                                                   #       = Ci * (H * S) + Hi * S + (Si - 1)
    129 
    130         # Calculate C/H/S according to LBA
    131         movw  $0x7bfa, %bp
    132         divw  2(%bp)                              # AX = Hi + H*Ci
    133                                                   # DX = Si - 1
    134         incw  %dx                                 # DX = Si
    135         pushw %dx                                 # 0000:7bfa = Si  <----
    136         xorw  %dx, %dx                            # DX:AX = Hi + H*Ci
    137         divw  4(%bp)                              # AX = Ci         <----
    138                                                   # DX = Hi         <----
    139 
    140 StartReadTo7C00:
    141 
    142         movb  (%bp), %cl                          # Si
    143         movb  %al, %ch                            # Ci[0-7]
    144         orb   %ah, %cl                            # Ci[8,9]
    145         movw  $0x7c00, %bx                        # ES:BX = 0000:7C00h
    146         movb  $0x2, %ah                           # Function 02h
    147         movb  $1, %al                             # 1 Sector
    148         movb  %dl, %dh                            # Hi
    149         movw  $0x600, %bp
    150         movb  PhysicalDrive(%bp), %dl             # Drive number
    151         int   $0x13
    152         jc    BadDbr
    153 
    154 
    155 
    156 # ****************************************************************************
    157 # Transfer control to BootSector - Jump to 0x0000:0x7C00
    158 # ****************************************************************************
    159         xorw  %ax, %ax
    160         pushw %ax                                 # PUSH 0x0000 - Segment
    161         movw  $0x7c00, %di
    162         pushw %di                                 # PUSH 0x7C00 - Offset
    163         retl                                      # JMP 0x0000:0x7C00
    164 
    165 # ****************************************************************************
    166 # ERROR Condition:
    167 # ****************************************************************************
    168 
    169 BadDbr:
    170     pushw %ax
    171     movw $0xb800, %ax
    172     movw %ax, %es
    173     movw $0x60, %ax
    174     movw %ax, %ds
    175     leaw %cs:ErrorString, %si
    176     movw $320, %di
    177     popw %ax
    178     call A2C
    179     movb %ah, 16(%si)
    180     movb %al, 18(%si)
    181     movw $10, %cx
    182     rep
    183     movsw
    184 Halt:
    185     jmp   Halt
    186 
    187 StartString:
    188 .byte 'M', 0x0c, 'B', 0x0c, 'R', 0x0c, ' ', 0x0c, 'S', 0x0c, 't', 0x0c, 'a', 0x0c, 'r', 0x0c, 't', 0x0c, '!', 0x0c
    189 ErrorString:
    190 .byte 'M', 0x0c, 'B', 0x0c, 'R', 0x0c, ' ', 0x0c, 'E', 0x0c, 'r', 0x0c, 'r', 0x0c, ':', 0x0c, '?', 0x0c, '?', 0x0c
    191 
    192 # ****************************************************************************
    193 # A2C - convert Ascii code stored in AH to character stored in AX
    194 # ****************************************************************************
    195 A2C:
    196     movb %ah, %al
    197     shrb $4, %ah
    198     andb $0xF, %al
    199     addb '0', %ah
    200     addb '0', %al
    201 
    202     cmpb '9', %ah
    203     jle  A2C_L1
    204     addb $7, %ah
    205 A2C_L1:
    206 
    207     cmpb '9', %al
    208     jle A2C_L2
    209     addb $7, %al
    210 A2C_L2:
    211     ret
    212 
    213 
    214 # ****************************************************************************
    215 # PhysicalDrive - Used to indicate which disk to be boot
    216 #                 Can be patched by tool
    217 # ****************************************************************************
    218 .org   0x01B6
    219 PhysicalDrive:        .byte 0x80
    220 
    221 # ****************************************************************************
    222 # MbrPartitionIndicator - Used to indicate which MBR partition to be boot
    223 #                         Can be patched by tool
    224 #                         OxFF means boot to legacy MBR. (LBA OFFSET 6)
    225 # ****************************************************************************
    226 .org   0x01B7
    227 MbrPartitionIndicator: .byte 0
    228 
    229 # ****************************************************************************
    230 # Unique MBR signature
    231 # ****************************************************************************
    232 .org   0x01B8
    233     .ascii "DUET"
    234 
    235 # ****************************************************************************
    236 # Unknown
    237 # ****************************************************************************
    238 .org   0x01BC
    239     .word 0
    240 
    241 # ****************************************************************************
    242 # MBR Entry - To be patched
    243 # ****************************************************************************
    244 .org   0x01BE
    245     .long 0,0,0,0
    246 .org   0x01CE
    247     .long 0,0,0,0
    248 .org   0x01DE
    249     .long 0,0,0,0
    250 .org   0x01EE
    251     .long 0,0,0,0
    252 
    253 # ****************************************************************************
    254 # Sector Signature
    255 # ****************************************************************************
    256 
    257 .org 0x01FE
    258 SectorSignature:
    259   .word     0xaa55      # Boot Sector Signature
    260 
    261 
    262 
    263