My new FAT32 bootloader

Question about which tools to use, bugs, the best way to implement a function, etc should go here. Don't forget to see if your question is answered in the wiki first! When in doubt post here.
Post Reply
User avatar
Firestryke31
Member
Member
Posts: 550
Joined: Sat Nov 29, 2008 1:07 pm
Location: Throw a dart at central Texas
Contact:

My new FAT32 bootloader

Post by Firestryke31 »

So, I've finished the new version of my FAT32 bootloader, which has a couple of features my old one didn't have. It should, in theory, be able to check if it was loaded from a partition or a flat disk and adjust the important offsets accordingly, but Windows doesn't seem to want to partition my 63MB disk image, and I'm a little nervous about testing it on real HW, so basically I can only confirm that the flat disk loading works. It also uses LBA instead of CHS like my old one. Unfortunately, it kind of assumes that the BIOS supports the LBA extension, because I have a grand total of 3 bytes left. I've also had to sacrifice readability in some places to get the code to fit.

My biggest request is tips for optimization, so anything you can give me would be nice. Also, telling me whether or not it would actually work on a partitioned hard drive would be great.

Code dump (The values in the BPB evaluate to 0x0101... to make copying and pasting the binary data easier):

Code: Select all

;; Stage 1 bootloader for Firebird O.S
;;  FAT32 Partition version
;;  Version 2.0
org 0x7C00
bits 16

BS_jmpBoot:
	jmp start
	nop

;; FAT fields, labeled here for convenience
BS_OEMName:
	dd 16843009
	dd 16843009
BPB_BytsPerSec:
	dw 257
BPB_SecPerClus:
	db 1
BPB_ResvdSecCnt:
	dw 257
BPB_NumFATs:
	db 1
BPB_RootEntCnt:
	dw 257
BPB_TotSec16:
	dw 257
BPB_Media:
	db 1
BPB_FATSz16:
	dw 257
BPB_SecPerTrk:
	dw 257
BPB_NumHeads:
	dw 257
BPB_HiddSec:
	dd 16843009
BPB_TotSec32:
	dd 16843009
BPB_FATSz32:
	dd 16843009
BPB_ExtFlags:
	;; Bits 0-3 = Active FAT, 7 = !FAT mirroring
	dw 257
BPB_FSVer:
	dw 257
BPB_RootClus:
	dd 16843009
BPB_FSInfo:
	dw 257
BPB_BkBootSec:
	dw 257
BPB_Reserved:
	dd 16843009
	dd 16843009
	dd 16843009
BS_DrvNum:
	db 1
BS_Reseved1:
	db 1
BS_BootSig:
	db 1
BS_VolID:
	dd 16843009
BS_VolLab:
	dd 16843009
	dd 16843009
	dw 257
	db 1
BS_FilSysType:
	dd 16843009
	dd 16843009

start:
	;; save DS so we can get the value at ds:si later
	push ds
	pop fs
	;; Set CS, DS, ES, & SS to a known value
	;; I used eax because I want to have the upper word cleared later
	xor eax, eax
	mov ds, ax
	mov es, ax
	jmp 0:loadCS
loadCS:
	
	;; set up the stack ( a temporary 512-byte stack )
	mov ss, ax
	mov sp, 0x8000
	mov bp, sp
	
	;; LBA packet
	mov [LBAindex+4], eax
	mov al, 16
	mov [LBApacket], ax

	;; Save the boot drive
	;; BootDrive = dl
	push dx
	
	;; check if we're on a partition
	xor al, al
	mov bx, bp
	mov cl, 1
	mov sp, LBApacketAddr
	call readDiskLBA
	lea sp, [BootDrive]
	;; Now to compare.
	;; If the sector we just loaded == this code,
	;; we're on a flat disk. Else, let's assume a partition
	mov si, 0x7C00
	mov di, bp
	mov cx, 512
	repe cmpsb
	;; get the partition start from the MBR
	mov ecx, [fs:si+8]
	jne .partitioned
	;; if we're here, it's not actually partitioned,
	;; so clear the 'offset'
	xor ecx, ecx
.partitioned:
	
	;; calculate the first data sector
	;; FirstDataSector = BPB_NumFATs * BPB_FATSz32 + BPB_ResvdSecCnt + partitionStart
	mov al, [BPB_NumFATs]
	mul dword [BPB_FATSz32]
	movzx ebx, word [BPB_ResvdSecCnt]
	add eax, ebx
	add eax, ecx
	push eax
	
	;; now let's get the location of the first FAT
	;; FATsector = BPB_ResvdSecCnt + partitionStart
	movzx eax, word [BPB_ResvdSecCnt]
	add eax, ecx
	push eax
	
	;; BytsPerCluster = BPB_BytsPerSec * BPB_SecPerClus
	mov ax, [BPB_BytsPerSec]
	mul word [BPB_SecPerClus]
	push eax
	
	;; FATClusterMask = 0x0FFFFFFF
	mov eax, 0x0FFFFFFF
	push eax
	
	;; FATEoFMask = 2nd 'cluster' value & (bitwise) FATClusterMask
	;; load the FAT
	mov eax, [FATsector]
	mov bx, bp
	mov cl, 1
	mov sp, LBApacketAddr
	call readDiskLBA
	lea sp, [FATClusterMask]
	;; Get the second cluster's value
	mov eax, [bp+4]
	and eax, [FATClusterMask]
	push eax
	
	;; CurrentCluster = BPB_RootClus
	mov eax, [BPB_RootClus]
	push eax
	
	;; Fortunately, clusters are relative to FirstDataSector
	
	;; Reserve the LBA packet,
	;; (even though we've already been using it)
	sub sp, byte 16
	
	mov di, bp
	;; Stack is now as follows:
BootDrive 			equ BP- 2
FirstDataSector		equ BP- 6
FATsector			equ BP-10
BytsPerCluster		equ BP-14
FATClusterMask		equ BP-18
FATEoFMask			equ BP-22
CurrentCluster		equ BP-26
LBAindex			equ BP-36
LBAseg				equ BP-38
LBAaddr				equ BP-40
LBAcount			equ BP-42
LBApacket			equ BP-44
LBApacketAddr		equ 0x8000-44
	
	;; Load the first root directory cluster
	call readCluster
	
	;; parse first cluster to see if it has what we want
nextDirCluster:
	;; Set bx to the end of the cluster
	mov bx, [BytsPerCluster]
	add bx, bp
	;; ax = 0x8000 - sizeof(FAT_DIR_entry)
	;; this simplifies the upcoming loop a bit
	lea ax, [bp-32]

findloop:
	;; move to next entry
	add ax, 32
	;; check if we're at the end of the cluster
	cmp ax, bx
	;; if so, handle it
	jz notFound
	;; I got 99 problems, bein' found is one.
	;; If you're havin' directory problems,
	;; I feel bad for you, son.
	
	;; (Too much?)
	
	;; else let's check the entry
	mov si, ax
	mov di, fileName
	mov cx, 11
	;; compare names
	repe cmpsb
	;; if not the same, try next entry
	jnz findloop
	
	;; file found!
	;; +9 and +15 because SI is already 11 bytes into the entry
	mov ax, [si+9]
	sal eax, 16
	mov ax, [si+15]
	;; eax = cluster of file
	mov [CurrentCluster], eax
	mov di, bp
loadFileLoop:
	;; if we're already at the EoF, this won't read anything
	call readCluster
	;; it will, however, set the carry flag to indicate that we're at the EoF
	;; so if( !cf )
	;;  keep loading clusters
	jnc loadFileLoop
	;; else
	;;  jump to the second stage
	jmp bp

notFound:
	;; try reading the next cluster
	call readCluster
	jnc nextDirCluster
	;; if this was the last one
	;; show an error
	mov si, noFile
	jmp putStr
	
;; A few useful routines	

;;  readCluster :: ES:DI = dest
readCluster:
	;; Check if we're already at the EoF
	mov eax, [CurrentCluster]
	and eax, [FATClusterMask]
	cmp eax, [FATEoFMask]
	;; if so, bail
	jz eofLoad
	
	;; Get the first sector of the cluster
	;; Sector = (cluster - 2) * BPB_SecPerClus + FirstDataSector
	sub eax, 2
	movzx ebx, byte [BPB_SecPerClus]
	mul ebx
	add eax, [FirstDataSector]
	;; eax = first sector of cluster
	;; fetch the cluster and put it where the user wanted
	mov bx, di
	mov cl, [BPB_SecPerClus]
	call readDiskLBA

	;; increment the destination pointer
	add di, [BytsPerCluster]
	
	;; we've trashed eax, so let's get it back
	;; so we can store the next cluster
	mov eax, [CurrentCluster]
	
	;; now, let's get the number of
	;; cluster pointers in a sector
	movzx ebx, word [BPB_BytsPerSec]
	shr bx, 2
	;; now that we have that, let's figure
	;; out the offset, in sectors, of the
	;; current cluster pointer
	xor edx, edx
	div eax, ebx
	;; now that we have those, let's save the clusterpointer index
	push dx
	;; add in the location of the first FAT sector
	;; to get the location on disk
	add eax, [FATsector]
	;; figure out where to put it
	mov bx, 0x7C00
	sub bx, [BPB_BytsPerSec]

	mov si, bx
	mov cl, 1
	call readDiskLBA
	
	pop dx
	;; dx = index of desired clusterpointer
	
	;; let's figure out the memory offset
	;; for the cluster pointer
	sal dx, 2
	add si, dx
	;; load the next cluster
	mov eax, [si]
	;; and set it to the new current cluster
	mov [CurrentCluster], eax
	
	;; clear the EoF flag and return
	clc
	ret
	
eofLoad:
	;; set the EoF flag and return
	stc
	ret

readDiskLBA:
	push si
	;; Set the LBA packet parameters
	mov [LBAindex], eax
	mov [LBAcount], cl
	mov [LBAseg], es
	mov [LBAaddr], bx
	;; set the error count to 0
	xor al, al
	push ax
.tryLoop:
	mov si, LBApacketAddr
	mov ah, 0x42
	mov dl, [BootDrive]
	int 13h
	jc .readError
	pop ax
	pop si
	ret


.readError:
	;; whoops! there was an error reading the drive!
	;; Let's check and see if we've already tried too many times
	
	;; grab the value
	pop ax
	inc al
	push ax
	
	;; It just so happens that the number of times we want to loop
	;; also can be used as the bit mask for comparing. How useful!
	and al, 0x04
	jz .tryLoop
	
freeze:
	;; Too many failures, display an error and freeze
	mov si, readFail
putStr:
	;; ah = useTeletype
	mov ah, 0x0E
	;; bh = use page 0, bl = useless in Bochs
	xor bx, bx
.loopPut:
	;; lodsb == mov al, si \ inc si
	;; too bad it doesn't do "or al, al" also
	lodsb
	;; check if al == 0
	or al, al
	;; if so, we're done
.here
	jz .here
	;; otherwise, let's put it
	int 10h
	;; and go again for the next character
	jmp .loopPut
	
;; Some basic data

readFail:
	db "Drive read failed!", 0
noFile:
	db "No FBOOT.SYS!", 0

fileName:
	db "FBOOT   SYS"

	;; this is here in case I make changes
	times 510-($-$$) db 0
	
	;; Standard end of boot sector
	db 0x55, 0xAA
Sorry for the long post...
Owner of Fawkes Software.
Wierd Al wrote: You think your Commodore 64 is really neato,
What kind of chip you got in there, a Dorito?
User avatar
abachler
Member
Member
Posts: 33
Joined: Thu Jan 15, 2009 2:21 pm

Re: My new FAT32 bootloader

Post by abachler »

Add code to differentiate between BIOS's that support CHS only or LBA. Here is the code I use in my MBR

Code: Select all

	; check for LBA BIOS extensions
	mov ah , 0x41
	mov bx , 0x55aa
	mov dl , 0x80
	int 0x13
	jnc lba_available
    
             ; CHS loader goes here
             jmp continue

lba_available:
             ; LBA loader goes here


continue:


User avatar
Firestryke31
Member
Member
Posts: 550
Joined: Sat Nov 29, 2008 1:07 pm
Location: Throw a dart at central Texas
Contact:

Re: My new FAT32 bootloader

Post by Firestryke31 »

I would, except I have 3 bytes left in the sector. I think the code you use is too big, so there's not much I can do about it... If you can tell me how to optimize my code down enough to put not only the check, but the LBA->CHS code too, then I'll do it.
Owner of Fawkes Software.
Wierd Al wrote: You think your Commodore 64 is really neato,
What kind of chip you got in there, a Dorito?
User avatar
Troy Martin
Member
Member
Posts: 1686
Joined: Fri Apr 18, 2008 4:40 pm
Location: Langley, Vancouver, BC, Canada
Contact:

Re: My new FAT32 bootloader

Post by Troy Martin »

Make all the LEAs into MOVs and just screw the brackets. That will drop a byte per instruction.

Try shortening your error messages as well, I bet you could spare a few bytes of space by shortening readFail.
Image
Image
Solar wrote:It keeps stunning me how friendly we - as a community - are towards people who start programming "their first OS" who don't even have a solid understanding of pointers, their compiler, or how a OS is structured.
I wish I could add more tex
Ready4Dis
Member
Member
Posts: 571
Joined: Sat Nov 18, 2006 9:11 am

Re: My new FAT32 bootloader

Post by Ready4Dis »

Firestryke31 wrote:So, I've finished the new version of my FAT32 bootloader, which has a couple of features my old one didn't have. It should, in theory, be able to check if it was loaded from a partition or a flat disk and adjust the important offsets accordingly, but Windows doesn't seem to want to partition my 63MB disk image, and I'm a little nervous about testing it on real HW, so basically I can only confirm that the flat disk loading works. It also uses LBA instead of CHS like my old one. Unfortunately, it kind of assumes that the BIOS supports the LBA extension, because I have a grand total of 3 bytes left. I've also had to sacrifice readability in some places to get the code to fit.

My biggest request is tips for optimization, so anything you can give me would be nice. Also, telling me whether or not it would actually work on a partitioned hard drive would be great.

Code dump (The values in the BPB evaluate to 0x0101... to make copying and pasting the binary data easier):

(snip)

Sorry for the long post...
exceptionally long quote cut down - Combuster


Ok, a few suggestions:

Why are you jumping to reset the code segment? Is there something wrong with leaving it where the bios left you? Second, you are pushing ds, and poping fs, saying you want to save ds:si, however, you later then overwrite si... what exactly are you saving this for? Says something about getting the MBR from the partition, but you manually set si == 0x7C00, if you are loaded at 0x7C00, you can assume ds == 0x00, no reason to store this, and if ds != 0x00 on bootup, your code will not function properly, because it'll be looking at ds:0x7c00, which would be an incorrect memory address. Also, this is incorrect how it is anyways, you are reading the MBR to 0x8000 if i'm reading correctly, yet your checking fs:si, which is 0x00:0x7C00+8, shouldn't it be 0x00:0x8000+8? Again, if you know you're loading it to 0x00:0x8000, why do you need to save ds? If the bios sets ds = 0x7c0, and you load to 0x00:0x8000, then try reading it at 0x7c0:0x8000, you will be reading bad memory (0xFC00). Removing the push and pop at the start saves 4-bytes. Also, removing fs:si, removes the segment override, so that's another byte

I spot this at least twice, this is 12 bytes at least, so 24 bytes total (2 instances)...
mov bx, bp
mov cl, 1
mov sp, LBApacketAddr
call readDiskLBA

Now, if you make that a function, and call it, you only have 12 bytes, plus 2 calls (3 bytes each, so 6 bytes), this saves you 24-18 = 6 bytes. Not a huge savings, but look for other instances of commonly used code that can be made smaller.

As mentioned above, get rid of the LEA's and just use mov's.

Any reason you're using SAL instead of SHL? Just curious on this one. I haven't read through the entirety of the code, and i'm reading it in this window, so there may be some obvious misses, but hopefully it'll get you started :).

Now, I would pretty much assume any disk large enough to require Fat32 probably has an MBR, even a disk with a single partition still has an MBR, so you may want to just assume it has an MBR, format your flat image to use an MBR, and remove the checking for an MBR and just assume it's got one. This will simplify a lot, and I don't know of any large disks in the real world that don't use MBR's.

My boot sector does not rely on a file system, so it's much 'simpler' than what you have here, it just assumes it's second stage is the next sector on the disk and sets up paging, builds memory map, goes into pmode, etc. The first sector supplies the second sector with a function to read a sector from disk, so my second sector is 100% identical for any file system or boot media as long as the first sector is setup properly. I have a custom MBR that I use that passes all the partition information over, if there is no partition information, it assumes it was booted without an MBR (so, my boot loader relies heavily on my custom MBR). My MBR allows me to boot into any partition I chose (tested on a real machine with windows 98, xp, ms-dos, and my own OS), all of which boot flawlessly. Not saying this is a better method, just trying to provoke thought. Of course having to over-write an MBR is not always the best bet, and testing was... well, not exactly fun :).
User avatar
Firestryke31
Member
Member
Posts: 550
Joined: Sat Nov 29, 2008 1:07 pm
Location: Throw a dart at central Texas
Contact:

Re: My new FAT32 bootloader

Post by Firestryke31 »

Actually, I've checked, and my assembler outputs the same amount for LEA and MOV. LEA sp, [bp-offset] and MOV sp, hardcoded_word both assemble to 3 bytes.

Code: Select all

   104 00000080 BCD47F                  mov sp, LBApacketAddr
...
   106 00000086 8D66FE                  lea sp, [BootDrive] ;; this is the same as mov sp, 0x8000-2, but without the hard-codedness
I didn't notice that duplicated code, thanks!

I also didn't notice that I overwrote SI, I'll fix that.

I use SAL instead of SHL because I saw it first in the alphabetically listed opcode... list.

Finally, Windows doesn't want to let me partition my boot image, and formatting it using Windows just does the flat format.
Owner of Fawkes Software.
Wierd Al wrote: You think your Commodore 64 is really neato,
What kind of chip you got in there, a Dorito?
Ready4Dis
Member
Member
Posts: 571
Joined: Sat Nov 18, 2006 9:11 am

Re: My new FAT32 bootloader

Post by Ready4Dis »

How are you mounting it? I have my MBR code, and Fat32 formatting code. I generate my own images, rather than letting something else format them. I create the image, install my MBR (with whatever partitions I chose at compile time), then run my formatting tool on it, telling it what format to format in (it supports fat12, 16, and 32). I pretty much write all my own utilities, I have used them to format a real disk, and my disk images. Pretty nifty, it allows me to play with different things, like I car have one copy of the File Allocation Table in my partitions, rather than 2. I can get rid of all the blank space in-between partitions that were leftovers from incompatible programs of yesteryear. My MBR allows me to multi-boot any OS, even if it's not a multi-boot OS, I can set any partition to active on boot-up, as long as the OS doesn't over-write my MBR (even if it does, I can install it back), it will boot and ask which partition to boot, and run fine. Having only a single copy of the FAT on large drives helps. I can also force any size cluster I want, it allows me to test out my file system code pretty heavily (and by writing the utility to format the disk, which can also copy files, reserve space for my boot loader + kernel image, etc), I learned a lot about how the file system worked under the controlled environment (I could boot into DOS/windows in bochs or on my real machine, and run chkdisk which would report errors of my formatted disks and allow me to format the disk and see what it was doing differently, or what it was expecting). I should really make my tools a bit more user friendly and give them out to people, i am sure most people could use something that could partition and format a flat image, or a real disk. I plan on adding them as applications to my OS once it gets a bit further along, so I can boot into my OS from say a floppy, and partition a hard drive, install my MBR, etc.


*** Edit ***
Instead of doing just a format, try running fdisk (you can boot into a version of dos using a bootable floppy dos image), and create the partitions that way, then format it using windows after the MBR is created.
User avatar
Firestryke31
Member
Member
Posts: 550
Joined: Sat Nov 29, 2008 1:07 pm
Location: Throw a dart at central Texas
Contact:

Re: My new FAT32 bootloader

Post by Firestryke31 »

I use IMdisk to mount it, but with the boot sector (at least, until I can get partcopy working) I manually copy the data in a hex editor.

I do have a real partition for my OS, but I want to wait to use that for a bit, until I can be 90% sure it'll work on RHW...
Owner of Fawkes Software.
Wierd Al wrote: You think your Commodore 64 is really neato,
What kind of chip you got in there, a Dorito?
Ready4Dis
Member
Member
Posts: 571
Joined: Sat Nov 18, 2006 9:11 am

Re: My new FAT32 bootloader

Post by Ready4Dis »

Firestryke31 wrote:I use IMdisk to mount it, but with the boot sector (at least, until I can get partcopy working) I manually copy the data in a hex editor.

I do have a real partition for my OS, but I want to wait to use that for a bit, until I can be 90% sure it'll work on RHW...

A very simply MBR wouldn't take much to dump into a hex editor. Once your drive is partitioned, windows should have no issues formatting a partition. You should be able to leave the device 100% empty, and go into windows logical disk manager, and create partitions on the blank disk, rather than formatting it in a hex editor by hand (unless it only mounts it as a disk drive, and not as a block device, I have never used IMdisk). If it mounts the image as a disk drive, there may not be much you can do, i don't mount my image at all, i just tell bochs where the flat file is, and use my own tools (or you can get a FD image of dos, and use it to format the disk for you).
User avatar
Firestryke31
Member
Member
Posts: 550
Joined: Sat Nov 29, 2008 1:07 pm
Location: Throw a dart at central Texas
Contact:

Re: My new FAT32 bootloader

Post by Firestryke31 »

Unfortunately IMdisk Virtual Disk Driver seems to mount it as a disk drive, not a block device. Or something. All I know is that when I partitioned the image in bochs using the FreeDOS fdisk, Windows refused to recognize the partitions when I mounted it.

Edit: Tried it on my laptop, and sadly it doesn't seem to like Darwin. If I can figure out why Darwin can chainload Vista but not my boot sector...

Other than that, it works with partitions! (Tested in Bochs and on a USB drive)
Owner of Fawkes Software.
Wierd Al wrote: You think your Commodore 64 is really neato,
What kind of chip you got in there, a Dorito?
Post Reply