writembr: Implement support for GPT partitions, #4028.

* This should support both GPT and MBR formatted partitions.
* To boot Haiku from a GPT partition, it must have the correct
  BFS UUID for the partition.
* Tools such as gdisk/gptfdisk can create partitions with
  the correct BFS UUID.
This commit is contained in:
Jessica Hamilton 2015-06-01 23:11:47 +12:00
parent 6ff95509c2
commit 11e8ecdd94
6 changed files with 482 additions and 420 deletions

View File

@ -134,3 +134,16 @@ actions BootStaticLibraryObjects
$(RM) "$(1)"
$(HAIKU_AR_$(TARGET_PACKAGING_ARCH)) -r "$(1)" "$(2)" ;
}
rule BuildMBR binary : source
{
SEARCH on $(source) = $(SUBDIR) ;
MakeLocateDebug $(binary) ;
Depends $(binary) : $(source) ;
}
actions BuildMBR
{
$(RM) $(1)
$(HAIKU_CC_$(HAIKU_PACKAGING_ARCH)) $(2) -o $(1) $(MBRFLAGS) -nostdlib -Xlinker --oformat=binary -Xlinker -S -Xlinker -N -Xlinker "-e start" -Xlinker "-Ttext=0x600"
}

View File

@ -4,19 +4,6 @@ HAIKU_ANYBOOT_DIR ?= $(HAIKU_DEFAULT_ANYBOOT_DIR) ;
HAIKU_ANYBOOT = $(HAIKU_ANYBOOT_NAME) ;
HAIKU_ANYBOOT_LABEL ?= $(HAIKU_DEFAULT_ANYBOOT_LABEL) ;
rule BuildAnybootMBR binary : source {
Depends $(binary) : $(source) ;
MBR_SOURCE on $(binary) = $(source) ;
BuildAnybootMBR1 $(binary) ;
}
actions BuildAnybootMBR1 {
$(RM) $(1)
$(HAIKU_NASM) -f bin $(MBR_SOURCE) -O5 -o $(1)
}
rule BuildAnybootImage anybootImage : mbrPart : isoPart : imageFile {
local anyboot = <build>anyboot ;
@ -33,8 +20,8 @@ actions BuildAnybootImage1 {
}
local baseMBR = base_mbr.bin ;
local mbrSource = [ FDirName $(HAIKU_TOP) src bin writembr mbr.nasm ] ;
BuildAnybootMBR $(baseMBR) : $(mbrSource) ;
local mbrSource = [ FDirName $(HAIKU_TOP) src bin writembr mbr.S ] ;
BuildMBR $(baseMBR) : $(mbrSource) ;
MakeLocate $(baseMBR) : $(HAIKU_OUTPUT_DIR) ;
MakeLocate $(HAIKU_ANYBOOT) : $(HAIKU_ANYBOOT_DIR) ;
BuildAnybootImage $(HAIKU_ANYBOOT) : $(baseMBR) : $(HAIKU_CD_BOOT_IMAGE)

View File

@ -4,12 +4,8 @@ UsePrivateHeaders kernel shared storage ;
UsePrivateSystemHeaders ;
# Assemble the MBR code, and convert it into a header file
NASMFLAGS on [ FGristFiles mbr.bin ] = -f bin -O5 -dMBR_CODE_ONLY=1 ;
SEARCH on mbr.nasm = [ FDirName $(HAIKU_TOP) src bin writembr ] ;
Object [ FGristFiles mbr.bin ] : mbr.nasm ;
MBRFLAGS on [ FGristFiles mbr.bin ] = -DMBR_CODE_ONLY ;
BuildMBR [ FGristFiles mbr.bin ] : mbr.S ;
DataFileToSourceFile [ FGristFiles MBR.h ] : [ FGristFiles mbr.bin ]
: kMBR : kMBRSize ;

View File

@ -9,10 +9,7 @@ Application writembr :
;
# Assemble the MBR code, and convert it into a header file
NASMFLAGS on [ FGristFiles mbr.bin ] = -f bin -O5 ;
Object [ FGristFiles mbr.bin ] : mbr.nasm ;
BuildMBR [ FGristFiles mbr.bin ] : mbr.S ;
DataFileToSourceFile [ FGristFiles MBR.h ] : [ FGristFiles mbr.bin ]
: kMBR : kMBRSize ;

464
src/bin/writembr/mbr.S Normal file
View File

@ -0,0 +1,464 @@
/*
* Partly from:
* $FreeBSD: src/sys/boot/i386/pmbr/pmbr.s,v 1.2 2007/11/26 21:29:59 jhb Exp $
*
* Copyright (c) 2007 Yahoo!, Inc.
* All rights reserved.
* Written by: John Baldwin <jhb@FreeBSD.org>
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. Neither the name of the author nor the names of any co-contributors
* may be used to endorse or promote products derived from this software
* without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*
*
* Partly from:
* $FreeBSD: src/sys/boot/i386/mbr/mbr.s,v 1.7 2004/08/28 08:39:35 yar Exp $
*
* Copyright (c) 1999 Robert Nordier
* All rights reserved.
*
* Redistribution and use in source and binary forms are freely
* permitted provided that the above copyright notice and this
* paragraph and the following disclaimer are duplicated in all
* such forms.
*
* This software is provided "AS IS" and without any express or
* implied warranties, including, without limitation, the implied
* warranties of merchantability and fitness for a particular
* purpose.
*
*
* "Hybridisation" and modifications for booting Haiku by Andre' Braga
* (me@andrebraga.com), with valuable input from Jean-Loïc Charroud
* (jcharroud@free.fr). The modifications contained herein are released into
* the Public Domain.
*
*
* A 432 bytes MBR IPL (Initial Program Loader) that looks for the UUID of
* a Haiku Boot GUID partition and boots it, falling back to MBR partitions if
* said UUID isn't found or if the (primary) GPT is corrupted or non-existent.
* Its usefulness is in being a versatile, "universal" IPL that supports
* both partitioning styles, allowing it to be used transparently and even
* facilitating the conversion between partitioning styles, should the need
* for more partitions or volumes over 2TiB arise (for instance when cloning
* an older disk to a newer, more capacious one).
* It also paves the way for Haiku to create and support booting from
* multiple volumes larger than 2TiB, which we're in the very privileged
* position of enjoying efficiently in the near future due to BFS. Another use
* case is taking a disk from a Intel EFI machine, plugging it on a BIOS
* machine and boot just fine; and vice-versa.
* As mentioned, if there are valid partitions defined in the MBR, and the
* primary GPT becomes corrupt, it can fall back to loading the MBR partition
* with the active flag set, if one is defined.
* Currently there's no provision for falling back to the GPT copy that
* lives in the end of the disk, due to the 512 bytes constraint; supporting
* this is unlikely given that the code is packed tight. An alternative would be
* disabling support for booting from MBR using BIOS calls other than Int13h
* function 42h, "Extended Read From Disk" (i.e., LBA mode). It's unlikely that
* any machine that Haiku supports won't have this BIOS function, but having an
* "universal" IPL should be quite useful to, say, people using Haiku to
* rewrite a corrupt MBR on another disk using the excellent DiskProbe.
* The number of sectors loaded depends on the boot style. Booting from a
* MBR partition assumes that the Partition Boot Record is one sector long,
* whereas booting from a GPT partition assumes a partition exclusive for a
* system loader and will either copy its entirety into memory starting from
* address 0x7c00, or will copy up to circa 545KiB, whichever is smaller. Thus,
* it remains compatible with the FreeBSD gptloader and should work for loading
* Bootman from an exclusive Haiku boot manager partition as well.
* It should be easy to adjust the UUID signature as needed. It lives at
* offset 0x1a0 (416), leaving plenty of space before the 32-bit disk signature
* at offset 0x1b8 (440), so compatibility with Microsoft Windows and other OSs
* is maintained.
*/
.set LOAD,0x7c00
.set EXEC,0x600
.set MAGIC,0xaa55
.set HANDSHAKE,0x55aa
.set SECSIZE,0x200
/* data offsets */
.set UUID,0x1a0
.set DISKSIG,0x1b8
.set PT_OFF,0x1be
.set GPTSTACK,EXEC+SECSIZE*4-8 /* Stack address */
.set LBABUF,GPTSTACK /* LBA address pointer buffer, */
/* 8 bytes long, after stack */
.set GPT_ADDR,LBABUF+8 /* GPT header address */
.set GPT_SIG,0 /* Signature offset from LBA 1 */
.set GPT_SIG_0,0x20494645 /* "EFI ", bswapped */
.set GPT_SIG_1,0x54524150 /* "PART", bswapped */
.set GPT_MYLBA,24 /* Offs of curr header copy addr */
.set GPT_PART_LBA,72 /* Offs of partitions start LBA */
.set GPT_NPART,80 /* Offs to number of partitions */
.set GPT_PART_SIZE,84 /* Offs to size of partition */
.set PART_ADDR,GPT_ADDR+SECSIZE /* GPT partition array addr. */
.set PART_TYPE,0
.set PART_START_LBA,32 /* Offs to 1st LBA on part entry */
.set PART_END_LBA,40 /* Offs to last LBA */
.set NHRDRV,0x475 /* Number of hard drives */
.globl start /* Entry point */
.code16
/*
* Setup the segment registers for flat addressing and setup the stack.
*/
start: cli /* Clear interrupts before relocation */
xorw %ax,%ax /* Zero */
movw %ax,%es /* Address */
movw %ax,%ds /* data */
movw %ax,%ss /* Set up */
movw $GPTSTACK,%sp /* stack */
std /* String ops set to decrement */
movw $LOAD,%si /* We'll clear working memory starting */
leaw -1(%si),%di /* from $LOAD-1 and stopping at EXEC. */
movw $(LOAD-EXEC-1),%cx /* In the end we have %si pointing */
rep stosb /* at LOAD and %di at EXEC. */
/*
* Relocate ourself to a lower address so that we have more room to load
* other sectors.
*/
reloc: cld /* String ops set to increment */
movw $SECSIZE,%cx /* Now we walk forward and relocate. */
rep movsb /* Tricky, but works great! */
/*
* Jump to the relocated code.
*/
jmp $0,$main /* Absolute address (far) jump */
/*
* Will land here; we're now at %cs = 0x0000 and %ip a little above 0x0600
*/
main: sti /* Re-enable interrupts */
#ifdef VALIDATE_DRV
/*
* Validate drive number in %dl. Certain BIOSes might not like it.
*/
validate_drv:
cmpb $0x80,%dl /* Drive valid? (>= 0x80) */
jb validate_drv.1 /* No */
movb NHRDRV,%dh /* Calculate the highest */
addb $0x80,%dh /* drive number available */
cmpb %dh,%dl /* Within range? */
jb test_extensions /* Yes, proceed */
validate_drv.1:
movb $0x80,%dl /* Else, assume drive 0x80 */
#endif
/*
* Test if BIOS supports Int13h extensions. If so, will try GPT scheme first.
* Else, sets flag (%dh = 1) and goes straight to MBR code.
* (%dl still contains the drive number from BIOS bootstrap)
*/
test_extensions:
movb $0,%dh /* We'll test for EDD extensions. */
/* LBA read (Int13,42) uses only */
/* %dl to get drive number and if */
/* we must fall back to CHS read */
/* (Int13,02), %dh receives head */
/* number, so it's clear to use */
/* %dh to hold a "use CHS" flag */
movw $HANDSHAKE,%bx /* EDD extensions magic number */
movb $0x41,%ah /* BIOS: EDD extensions */
int $0x13 /* present? */
jc set_chs /* No, fall back to CHS read */
test_magic:
cmpw $MAGIC,%bx /* Magic ok? */
jne set_chs /* No, fall back to CHS read */
test_packet:
testb $0x1,%cl /* Packet mode present? */
jnz load_gpt_hdr /* Yes! */
set_chs:
movb $1,%dh /* read_chs overwrites this, and */
/* Int13,42 only uses %dl, so */
/* it's clear to use %dh as flag */
jmp try_mbr
/*
* If we reached here, drive is valid, LBA reads are available, will try GPT.
* Load the primary GPT header from LBA 1 and verify signature.
*/
load_gpt_hdr:
movw $GPT_ADDR,%bx
movw $LBABUF,%si /* Will load LBA sector 1 from disk */
movb $1,(%si) /* (64-bit value! Memory was zeroed so */
/* it's OK to write only the LSB) */
call read
cmpl $GPT_SIG_0,GPT_ADDR+GPT_SIG
jnz try_mbr /* If invalid GPT header */
cmpl $GPT_SIG_1,GPT_ADDR+GPT_SIG+4
jnz try_mbr /* Fluke :( Try MBR now */
/*
* GPT is valid. Load a partition table sector from disk and look for a
* partition matching the UUID found in boot_uuid.
*/
load_part:
movw $GPT_ADDR+GPT_PART_LBA,%si
movw $PART_ADDR,%bx
call read
scan:
movw %bx,%si /* Compare partition UUID */
movw $boot_uuid,%di /* with Haiku boot UUID */
movb $0x10,%cl /* (16 bytes) */
repe cmpsb
jnz next_part /* Didn't match, next partition */
/*
* We found a partition. Load it into RAM starting at 0x7c00.
*/
movw %bx,%di /* Save partition pointer in %di */
leaw PART_START_LBA(%di),%si
movw $LOAD/16,%bx
movw %bx,%es
xorw %bx,%bx
load_bootcode:
push %si /* Save %si */
call read
pop %si /* Restore */
movl PART_END_LBA(%di),%eax /* See if this was the last LBA */
cmpl (%si),%eax
jnz next_boot_lba
movl PART_END_LBA+4(%di),%eax
cmpl 4(%si),%eax
jnz next_boot_lba
jmp start_loader /* Jump to boot code */
next_boot_lba:
incl (%si) /* Next LBA */
adcl $0,4(%si)
mov %es,%ax /* Adjust segment for next */
addw $SECSIZE/16,%ax /* sector */
cmp $0x9000,%ax /* Don't load past 0x90000, */
jae start_loader /* 545k should be enough for */
mov %ax,%es /* any boot code. :) */
jmp load_bootcode
/*
* Move to the next partition. If we walk off the end of the sector, load
* the next sector.
*/
next_part:
decl GPT_ADDR+GPT_NPART /* Was this the last partition? */
jz try_mbr /* UUID boot signature not found */
movw GPT_ADDR+GPT_PART_SIZE,%ax
addw %ax,%bx /* Next partition */
cmpw $PART_ADDR+0x200,%bx /* Still in sector? */
jb scan
incl GPT_ADDR+GPT_PART_LBA /* Next sector */
adcl $0,GPT_ADDR+GPT_PART_LBA+4
jmp load_part
/*
* If loading boot sectors from a GPT partition fails, try booting a MBR part.
* Reset stack/segment. Could have been tainted by the GPT loading code.
*/
try_mbr:
xorw %ax,%ax /* Zero */
movw %ax,%es /* extra segment */
movw $LOAD,%sp /* Reset stack */
xorw %si,%si /* Will point to active partition */
movw $(EXEC+PT_OFF),%bx /* Point to partition table start */
movw $0x4,%cx /* Tested entries counter (4 total) */
read_mbr_entry:
cmpb %ch,(%bx) /* Null entry? (%ch just zeroed) */
je next_mbr_entry /* Yes */
jg err_part_table /* If 0x1..0x7f */
testw %si,%si /* Active already found? */
jnz err_part_table /* Yes */
movw %bx,%si /* Point to active */
next_mbr_entry:
addb $0x10,%bl /* Till */
loop read_mbr_entry /* done */
testw %si,%si /* Active found? */
jnz read_bootsect /* Yes, read OS loader */
try_diskless:
int $0x18 /* Else, BIOS: Diskless boot */
/*
* Ok, now that we have a valid drive and partition entry, load either CHS
* or LBA from the partition entry and read the boot sector from the partition.
*/
read_bootsect:
movw %sp,%bx /* Write addr. (%sp points to LOAD) */
pushw %si /* Points at active part. entry; */
/* save, else 'read' will trash it */
test_flag:
cmpb $1,%dh /* Test flag set by set_chs above */
jz read_chs /* CHS read if set */
read_lba:
addw $0x8,%si /* Start LBA of partition, 32-bit */
movw $LBABUF,%di /* So far either QWORD 1 or 0, so */
movsl /* more significant bytes are all 0 */
xchg %di,%si /* Copy to buffer and swap pointers */
subw $0x4,%si /* Adjust back to start of buffer */
call read
jmp finished_read /* Skip the CHS setup */
read_chs:
movb 0x1(%si),%dh /* Load head */
movw 0x2(%si),%cx /* Load cylinder:sector */
movb $2,%al /* Read two sectors */
movb $2,%ah /* BIOS: Read sectors from disk */
int $0x13 /* Call the BIOS */
finished_read:
jc err_reading /* If error */
/*
* Now that we've loaded the bootstrap, check for the 0xaa55 signature. If it
* is present, execute the bootstrap we just loaded.
*/
popw %si /* Restore %si (active part entry) */
movb %dl,(%si) /* Patch part record with drive num */
cmpw $MAGIC,0x1fe(%bx) /* Bootable? */
jne err_noboot /* No, error out. */
/* Else, start loader */
start_loader:
xorw %ax,%ax
movw %ax,%es /* Reset %es to zero */
jmp $0,$LOAD /* Jump to boot code */
/* Auxiliary functions */
/*
* Load a sector (64-bit LBA at %si) from disk %dl into %es:%bx by creating
* a EDD packet on the stack and passing it to the BIOS. Trashes %ax and %si.
*/
read:
pushl 0x4(%si) /* Set the LBA */
pushl 0x0(%si) /* address */
pushw %es /* Set the address of */
pushw %bx /* the transfer buffer */
pushw $0x1 /* Read 1 sector */
pushw $0x10 /* Packet length */
movw %sp,%si /* Packet pointer */
movw $0x4200,%ax /* BIOS: LBA Read from disk */
int $0x13 /* Call the BIOS */
add $0x10,%sp /* Restore stack */
jc err_reading /* If error */
ret
/*
* Output an ASCIZ string pointed at by %si to the console via the BIOS.
*/
putstr.0:
movw $0x7,%bx /* Page:attribute */
movb $0xe,%ah /* BIOS: Display */
int $0x10 /* character */
putstr:
lodsb /* Get character */
testb %al,%al /* End of string? */
jnz putstr.0 /* No */
ret
/*
* Various error message entry points.
*/
err_part_table:
movw $msg_badtable,%si /* "Bad Part. Table!" */
call putstr
jmp halt
err_reading:
movw $msg_ioerror,%si /* "Read Error!" */
call putstr
jmp halt
err_noboot:
movw $msg_noloader,%si /* "No Sys Loader!" */
call putstr
/* fall-through to halt */
halt:
cli
hlt
jmp halt
/* Data section */
#ifdef VALIDATE_DRV
/* Messages must be shortened so the code fits 440 bytes */
msg_badtable: .asciz "BadPTbl!"
msg_ioerror: .asciz "IOErr!"
msg_noloader: .asciz "NoSysLdr!"
#else
msg_badtable: .asciz "Bad Part. Table!"
msg_ioerror: .asciz "Read Error!"
msg_noloader: .asciz "No Sys Loader!"
#endif
/* Boot partition UUID signature */
.org UUID,0x0 /* Zero-pad up to UUID offset */
boot_uuid:
.long 0x42465331 /* 'BFS1' (formally, UUID time-low) */
.word 0x3ba3 /* UUID time-mid */
.word 0x10f1 /* UUID time-high & version (v1) */
.byte 0x80 /* UUID DCE 1.1 variant */
.byte 0x2a /* '*' (formally, UUID clock-seq-low) */
.byte 0x48 /* 'H' */
.byte 0x61 /* 'a' */
.byte 0x69 /* 'i' */
.byte 0x6b /* 'k' */
.byte 0x75 /* 'u' */
.byte 0x21 /* '!' */
#ifndef MBR_CODE_ONLY
/* Disk signature */
.org DISKSIG,0x0 /* Zero-pad up to signature offset */
sig:
.long 0 /* OS Disk Signature */
.word 0 /* "Unknown" in PMBR */
/* Partition table */
.org PT_OFF,0x0 /* Won't pad, just documenting */
partbl:
.fill 0x10,0x4,0x0 /* Partition table */
.word MAGIC /* Magic number */
#endif

View File

@ -1,395 +0,0 @@
; Copyright 2011, Jean-Loïc Charroud, jcharroud@free.fr
; Distributed under the terms of the MIT License or LGPL v3
;
; Haiku (C) Copyright Haiku 2011
; MBR Boot code
;
; assemble the Master boot record with:
; nasm -f bin -O5 -o mbr.bin mbr.S
;
; assemble the MBR's code (does not contain the partiton table
; nor the MAGIC code) with:
; nasm -f bin -O5 -o mbrcode.bin mbr.S -dMBR_CODE_ONLY=1
;%define DEBUG 1
;%define MBR_CODE_ONLY 1
;CONST
%assign DISKSIG 440 ; Disk signature offset
%assign PT_OFF 0x1be ; Partition table offset
%assign MAGIC_OFF 0x1fe ; Magic offset
%assign MAGIC 0xaa55 ; Magic bootable signature
%assign SECSIZE 0x200 ; Size of a single disk sector
%assign FLG_ACTIVE 0x80 ; active partition flag
%assign SECTOR_COUNT 0x01 ; Number of record to load from
; the ctive partition
%assign LOAD 0x7c00 ; Load address
%assign EXEC 0x600 ; Execution address
%assign HEAP EXEC+SECSIZE ; Execution address
;BIOS calls
%assign BIOS_VIDEO_SERVICES 0x10; ah - function
%assign BIOS_DISK_SERVICES 0x13
%assign BIOS_KEYBOARD_SERVICES 0X16
%assign BIOS_BASIC 0X18
%assign BIOS_REBOOT 0X19
;BIOS calls parameters
; video services
%assign WRITE_CHAR 0x0e; al - char
; bh - page?
; disk services
%assign READ_DISK_SECTORS 0x02; dl - drive
; es:bx - buffer
; dh - head
; ch7:0 - track7:0
; cl7:6 - track9:8
; 5:0 - sector
; al - sector count
; -> al - sectors read
%assign READ_DRV_PARAMETERS 0x08; dl - drive
; -> cl - max cylinder 9:8
; - sectors per track
; ch - max cylinder 7:0
; dh - max head
; dl - number of drives (?)
%assign CHK_DISK_EXTENTIONS 0x41; bx - 0x55aa
; dl - drive
; -> success: carry clear
; ah - extension version
; bx - 0xaa55
; cx - support bit mask
; 1 - Device Access using the
; packet structure
; 2 - Drive Locking and
; Ejecting
; 4 - Enhanced Disk Drive
; Support (EDD)
; -> error: carry set
%assign EXTENDED_READ 0x42; dl - drive
; ds:si - address packet
; -> success: carry clear
; -> error: carry set
%assign FIXED_DSK_SUPPORT 0x1 ; flag indicating fixed disk
; extension command subset
; keyboard services
%assign READ_CHAR 0x00; -> al - ASCII char
;MACRO
; nicer way to get the size of a structure
%define sizeof(s) s %+ _size
; using a structure in a another structure definition
%macro nstruc 1-2 1
resb sizeof(%1) * %2
%endmacro
; nicer way to access GlobalVariables
%macro declare_var 1
%define %1 HEAP + GlobalVariables. %+ %1
%endmacro
%macro puts 1
mov si, %1
call _puts
%endmacro
%macro error 1
mov si, %1
jmp _error
%endmacro
;TYPEDEFS
; 64 bit value
struc quadword
.lower resd 1
.upper resd 1
endstruc
struc CHS_addr
.head resb 1
.sector resb 1
.cylindre resb 1
endstruc
struc PartitionEntry
.status resb 1
.CHS_first nstruc CHS_addr
.type resb 1
.CHS_last nstruc CHS_addr
.LBA_start resd 1
.LBA_size resd 1
endstruc
; address packet as required by the EXTENDED_READ BIOS call
struc AddressPacket
.packet_size resb 1
.reserved resb 1
.block_count resw 1
.buffer resd 1
.sector nstruc quadword
;.long_buffer nstruc quadword
; We don't need the 64 bit buffer pointer. The 32 bit .buffer is more
; than sufficient.
endstruc
; Structure containing the variables that don't need pre-initialization.
; this structure will be allocated onto our "heap".
struc GlobalVariables
.boot_drive_id resd 1
.boot_partition resd 1
.address_packet nstruc AddressPacket
endstruc
;alias for easy access to our global variables
declare_var boot_drive_id
declare_var boot_partition
declare_var address_packet
;/////////////////////////////////////////////////////////////////////////
;// A 512 byte MBR boot manager that simply boots the active partition. //
;/////////////////////////////////////////////////////////////////////////
; 16 bit code
SECTION .text
BITS 16
ORG EXEC ; MBR is loaded at 0x7c00 but relocated at 0x600
start: ; we run the LOADed code
cli ; disable interrupts
cld ; clear direction flag (for string operations)
init:
xor ax, ax ; Zero
mov es, ax ; Set up extra segment
mov ds, ax ; Set up data segment
mov ss, ax ; Set up stack segment
mov sp, LOAD ; Set up stack pointer
;init our heap allocated variables with zeros
mov di, HEAP ;start adress
mov cx, sizeof(GlobalVariables) ;size
rep ; while(cx--)
stosb ; es[di++]:=al;
; Relocate ourself to a lower address so that we are out of the way
; when we load in the bootstrap from the partition to boot.
reloc:
mov si, LOAD ; Source
; init AddressPacket.buffer now since LOAD is in 'si'
mov [address_packet+AddressPacket.buffer],si
mov byte[address_packet+AddressPacket.packet_size],sizeof(AddressPacket)
mov byte[address_packet+AddressPacket.block_count],SECTOR_COUNT
mov di, EXEC ; Destination
mov ch, 1 ; count cx:=256 (cl cleared by precedent rep call)
rep ; while(cx--)
movsw ; es[di++]:=ds[si++]
; //di and si are incremented by sizeof(word)
jmp word 0x0000:continue; FAR jump to the relocated "continue" (some
; BIOSes initialise CS to 0x07c0 so we must set
; CS correctly)
continue: ; Now we run EXEC_based relocated code
sti ; enable interrupts
%ifdef DEBUG
puts kMsgStart
%endif
search_active_partition:
mov si,EXEC+PT_OFF ; point to first table entry
mov al,04 ; there are 4 table entries
.loop: ; SEARCH FOR AN ACTIVE ENTRY
cmp byte[si],FLG_ACTIVE ; is this the active entry?
je found_active ; yes
add si, sizeof(PartitionEntry) ; next PartitionEntry
dec al ; decrease remaining entry count
jnz .loop ; loop if entry count > 0
jmp no_bootable_active_partition; last partition reached
found_active: ; active partition (pointed by si)
mov [boot_partition],si ; Save active partition pointer
.get_read_sector: ; initialise address_packet:
mov eax,[si + PartitionEntry.LBA_start]
mov [address_packet+AddressPacket.sector],eax
; if LBA_adress equals 0 then it's not a valid PBR (it is the MBR)
; this can happen when we only have a CHS adress in the partition entry
test eax, eax ;if ( LBA_adress == 0 )
jz no_disk_extentions ;then no_disk_extentions()
check_disk_extensions:
; Note: this test may be unnecessary since EXTENDED_READ also
; set the carry flag when extended calls are not supported
%ifdef DEBUG
puts kMsgCheckEx
%endif
mov ah, CHK_DISK_EXTENTIONS ; set command
mov bx, 0x55aa ; set parameter : hton(MAGIC)
; dl has not changed yet, still contains the drive ID
int BIOS_DISK_SERVICES ; if( do_command() <> OK )
jc no_disk_extentions ; then use simple read operation
; else use extended read
disk_extentions:
%ifdef DEBUG
puts kMsgRead_Ex
%endif
; load first bloc active partition
; dl has not changed yet, still contains the drive ID
mov si, address_packet ; set command parameters
mov ah, EXTENDED_READ ; set command
.read_PBR:
int BIOS_DISK_SERVICES ; if ( do_command() <> OK )
jc no_disk_extentions ; then try CHS_read();
check_for_bootable_partition:
cmp word[LOAD+MAGIC_OFF],MAGIC ; if ( ! volume.isBootable() )
jne no_bootable_active_partition; then error();
jump_PBR:
%ifdef DEBUG
puts kMsgBootPBR
call _pause
%else
puts kMsgStart
%endif
; jump to 0x7c00 with :
; - CS=0
; - DL=drive number
; - DS:SI=pointer to the selected partition table
; entry (required by some PBR)
; dl has not changed yet, still contains the drive ID
mov si, [boot_partition]
jmp LOAD ; jump into partition boot loader
no_disk_extentions:
%ifdef DEBUG
puts kMsgNoExtentions
%endif
mov si, [boot_partition] ; Restore active partition pointer
;load CHS PBR sector info
mov dh, [si+1] ; dh 7:0 = head 7:0 (0 - 255)
mov cx, [si+2] ; cl 5:0 = sector 7:0 (1 - 63)
; cl 7:6 = cylinder 9:8 (0 - 1023)
; ch 7:0 = cylinder 7:0
.check_Sector:
mov al, cl
and al, 0x3F ; extract sector
test al, al; ; if (sector==0)
jz no_bootable_active_partition; then error("invalid sector");
cmp al, 0x3F ; if( (Sector == 63)
jne .CHS_valid ;
.check_Cylinder:
mov ax, cx
shr ah, 6
cmp ax, 0x03FF ; and (Cylinder == 1023)
jne .CHS_valid
.check_Head:
cmp dh, 0xFF ; and ( (Head == 255)
jne .CHS_valid
cmp dh, 0xFE ; or (Head == 254) ) )
je no_bootable_active_partition; then error("invalid CHS_adress");
.CHS_valid:
; dl has not changed yet, still contains the drive ID
mov bx, LOAD ; set buffer
mov al, SECTOR_COUNT ; set Size
mov ah, READ_DISK_SECTORS ; set read command
int BIOS_DISK_SERVICES ; if ( do_command() == OK )
jnc check_for_bootable_partition; then resume(normal boot sequence)
; else continue;
no_bootable_active_partition:
mov si, kMsgNoBootable
;jmp _error ; _error is the next line !
_error:
; display a non-empty null-terminated string on the screen,
; wait for a key pressed and go back to the bios
; IN :
; - si = address of string to display
; OUT :
; DIRTY :
; - ax
; - si
call _puts
call _pause
puts kMsgROMBASIC
int BIOS_BASIC ; BIOS_BASIC give the control back
; to the BIOS. Doing so, let some
; BIOSes try to boot an alternate
; device (PXE/CD/HDD : see your
; BIOS' boot device order )
_pause:
; wait for a key pressed
; IN :
; OUT :
; DIRTY :
; - ax
mov ah, READ_CHAR
int BIOS_KEYBOARD_SERVICES
ret
_puts:
; display a non-empty null-terminated string on the screen
; IN :
; - si = address of string to display
; OUT :
; DIRTY :
; - ax
; - bx
; - si
xor bx, bx ; bx:=0
.loop: ; do {
lodsb ; al=[si++];
mov ah, WRITE_CHAR ;
int BIOS_VIDEO_SERVICES ; WRITE_CHAR(al)
or al, al ; } while (al<>0);
jnz .loop
ret
data:
kMsgROMBASIC db 'ROM BASIC',0
kMsgNoBootable db 'No bootable active volume',13,10,0
kMsgStart db 'Loading system',10,13,0
%ifdef DEBUG
kMsgBootPBR db 'JMP PBR',13,10,0
kMsgRead_Ex db 'Read_ex block',13,10,0
kMsgCheckEx db 'CheckEx',13,10,0
kMsgNoExtentions db 'Read block',13,10,0
kMsgReloc db 'reloc MBR',13,10,0
%endif
; check whether the code is small enough to fit in the boot code area
end:
%if end - start > DISKSIG
%error "Code exceeds master boot code area!"
%endif
%ifdef MBR_CODE_ONLY
;just build the code.
;Do not generate the datas
%else
%rep start + DISKSIG - end
db 0 ;fill the rest of the code area
%endrep
kMbrDiskID dd 0 ;Disk signature
dw 0 ;reserved
PartitionTable times PartitionEntry_size * 4 db 0
DiskSignature:
%if DiskSignature - start <> MAGIC_OFF
%error "incorrect Disk Signature offset"
%endif
kMbrSignature db 0x55, 0xAA
%endif