CLOSE

In the last article, we ported our stage 1 to ISO 9660 File System, read and print the content of sample (ab.txt) text file. This article is all about the stage2 loader. We will load the stage2 loader from the stage1 and jump to it.

Some Important Information about Stage2

  • It would be in plain binary format.
  • It would be loaded at memory location 0x0500. There is 29KB of free space starting at address 0x0500 - 0x7AFF. This region is only for stage2 loader.
  • The stage2 loader file is named STAGE2.BIN. When compiled, its file identifier is stage2.bin. However, in the ISO 9660 file system, all file names are converted to uppercase.

Code to Load Stage2 Loader:

There are little changes from the last article code. I will not go in depth of every code, will give a brief summary of everything.

stage1.asm:

BITS 16
ORG 0x7C00

stage1_start:

jmp main

; Memory Map:
; 0x00000000 - 0x000003FF	Reserved (1KB), Real Mode IVT (Interrupt Vector Table)
; 0x00000400 - 0x000004FF	Reserved (256 bytes), BDA (BIOS Data Area)
; 0x00000500 - 0x00007AFF	Second Stage Bootloader (~29 Kb)
; 0x00007B00 - 0x00007BFF	Stack Space (256 Bytes)
; 0x00007C00 - 0x0000CBFF	ISO Stage1 Bootloader (20 KiloBytes = 20,480 bytes)
; 0x0000CC00 - 0x0007FFFF	460 KB, File Loading.
; 0x00080000 - 0x0009FFFF	128 KB, Can be used by subsystems in this bootloader
			; This memory will be known as the Subsystem memory area
			; It can be accesses with segment:offset
			; segment = 0x8000, offset = 0x00
			; Thus complete address => segement*16 + offset
			; 0x8000 * 16 + 0 = 0x80000
; 0x000A0000 - 0x000BFFFF	128 KB, Video Display Memory, reserved
; 0x000C0000 - 0x000C7FFF	32 KB, Video BIOS
; 0x000C8000 - 0x000EFFFF	160 KB BIOS Expansion
; 0x000F0000 - 0x000FFFFF	64 KB Motherboard BIOS

%define STAGE2_AREA_SEGMENT	0x0000
%define STAGE2_AREA_OFFSET	0x0500

%define SUBSYSTEM_MEM_SEGEMENT 0x8000
%define SUBSYSTEM_MEM_OFFSET 0x00
%define FILE_LOADING_AREA_MEM_SEGMENT 0xCC00
%define FILE_LOADING_AREA_MEM_OFFSET 0x0000	; It is the file loading area in memory map

;; Note: In order to access the memory above 0xFFFF, we need to use the combination of
;;	segment: offset, such that by default es is set to 0x00 and with this
;;	we can have offset of from 0x0000 to 0xFFFF. We can't access more than this
;;	with the segment set to 0x0000, which is the limit of every segment window
;;	64 KB. Thus suppose we need to access the 0x10000 which is above the 64 KB
;;	mark of the default segment: offset when segment set to 0x00.
;;	In order to access the 0x10000, we can set segment (like es) to 0x1000 and
;;	offset to 0x00 (like si). Thus es:si = 0x1000:0x0000 = 0x1000*16 + 0x0000
;;	= 0x10000

; Includes
%include "defines.inc"	; For constants and common variables
%include "print16.inc"	; For printing functions
%include "disk.inc"		; For disk read function
%include "iso9660.inc"		; For ISO 9660 file system

main:
	; Disable Interrupts, unsafe passage
	cli

	; Far jump to fix segment registers
	jmp 	0x0:FixCS

FixCS:
	; Fix segment registers to 0
	xor 	ax, ax
	mov	ds, ax
	mov	es, ax

	; Set stack
	; The sp register is used to point to the top of the stack. By setting sp to 0x7C00, the bootloader ensures that the stack starts at the top of the memory allocated for the bootloader. This is important because the stack grows downward in memory, so it's set up before any other code runs.
	mov	ss, ax
	mov	ax, 0x7C00	; It ensure that there's space for the stack to grow downward without overlapping with other code or any other data in memory.
	mov	sp, ax

	; set interrupts
	sti

	; Save the DL register value, which contains the disk number 
	mov 	byte [bPhysicalDriveNum], dl

	call ClearScreenAndResetCursor	; Clear the screen and reset the cursor



	;Print Welcome to the Screen
	mov si, WelcomeToStage1		; Load the address of the string into si register
	call PrintString16BIOS		; String printing function.
	call PrintNewline		; \n


	;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
	;; Calculate and print the actual code size of stage1
	; The actual code is without padding, from start to the right before the
	; ending times statement.
	mov ax, actual_code_end - stage1_start
	mov si, sActualStage1SizeStatement
	call PrintString16BIOS
	call PrintWordNumber
	call PrintNewline

	;; Calculate and print the padded code size of stage1
	; The padded code is with padding, from start to the very end line
	; after the times statement.
	mov ax, stage1_end - stage1_start
	mov si, sPaddedStage1SizeStatement
	call PrintString16BIOS
	call PrintWordNumber
	call PrintNewline
	;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

	;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
	;; calculate and print the size of PVD structure, for debugging purpose only.
	; It should be 2048 bytes
	; mov ax, PrimaryVolumeDescriptor.PVD_End - PrimaryVolumeDescriptor
	; call PrintWordNumber
	; call PrintNewline	; '\n'
	;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

	;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
	;; ISO 9660 things...
	; Read the ISO 9660
	call Read_volume_descriptors
	;; TODO, there should be way to check for the success and failure of above function
	;	on return, because the below functions depends on it.

	; Search for the file whose name is stored at SampleTextFileIdentifier location
	; and load it at FILE_LOADING_AREA_MEM_SEGMENT:FILE_LOADING_AREA_MEM_OFFSET
	; and print its content.

	;; Segment of Root Directory Record (Entry) in es
	xor eax, eax
	mov ax, SUBSYSTEM_MEM_SEGEMENT	;
	mov es, ax
	;; Offset of Root Directory Record (Entry) in si
	mov si, SUBSYSTEM_MEM_OFFSET	; 0x0000

	;; Segment of file load in fs
	xor bx, bx
	mov bx, STAGE2_AREA_SEGMENT	; 0x0000
	mov fs, bx
	;; Offset of file load in di
	mov di, STAGE2_AREA_OFFSET	; 0x0500

	mov ax, Stage2FileIdentifier		; file identifier
	mov cx, Stage2FileIdentifierLength	; file identifier length
	call Find_and_Load_File_from_Root
	
;; Jump to the loaded binary stage2
	; jump to the stage 2 land
	jmp STAGE2_AREA_SEGMENT:STAGE2_AREA_OFFSET	; 0x0000:0x0500

	; Infinite loop
	jmp $


; **************************
; Variables
; **************************
bPhysicalDriveNum	db	0	; Define variable to store disk number	

WelcomeToStage1	db 'Welcome to the Stage1', 0	; Define welcome message
sPassedDriveNumber db	'Passed Drive Number from Stage1 : ', 0
sActualStage1SizeStatement db 'Actual size of the stage1 code (without padding in bytes): ', 0
sPaddedStage1SizeStatement db 'Padded size of the stage1 code (with padding in bytes): ', 0

;; Sample Text File
SampleTextFileIdentifier: db 'AB.TXT', 0
SampleTextFileIdentifierLength equ $ - SampleTextFileIdentifier - 1	; -1 is for the null terminator 

;; Stage 2 Bin File
Stage2FileIdentifier: db 'STAGE2.BIN', 0
Stage2FileIdentifierLength equ $ - Stage2FileIdentifier - 1	; -1 is for the null terminator 





PrimaryVolumeDescriptor:
    .PVD_Type               db 0                  ; 1 byte: Volume Descriptor Type
    .PVD_StandardIdentifier db 5 dup(0)           ; 5 bytes: Standard Identifier (CD001)
    .PVD_Version            db 0                  ; 1 byte: Volume Descriptor Version
    .PVD_Unused1            db 1 dup(0)           ; 1 byte: Unused Field
    .PVD_SystemIdentifier   db 32 dup(0)          ; 32 bytes: System Identifier
    .PVD_VolumeIdentifier   db 32 dup(0)          ; 32 bytes: Volume Identifier
    .PVD_Unused2            db 8 dup(0)           ; 8 bytes: Unused Field
    .PVD_VolumeSpaceSize    dd 0                  ; 4 bytes: Volume Space Size (little-endian)
    .PVD_VolumeSpaceSizeBE  dd 0                  ; 4 bytes: Volume Space Size (big-endian)
    .PVD_Unused3            db 32 dup(0)          ; 32 bytes: Unused Field
    .PVD_VolumeSetSize      dw 0                  ; 2 bytes: Volume Set Size (little-endian)
    .PVD_VolumeSetSizeBE    dw 0                  ; 2 bytes: Volume Set Size (big-endian)
    .PVD_VolumeSequenceNumber dw 0                ; 2 bytes: Volume Sequence Number (little-endian)
    .PVD_VolumeSequenceNumberBE dw 0              ; 2 bytes: Volume Sequence Number (big-endian)
    .PVD_LogicalBlockSize   dw 0                  ; 2 bytes: Logical Block Size (little-endian)
    .PVD_LogicalBlockSizeBE dw 0                  ; 2 bytes: Logical Block Size (big-endian)
    .PVD_PathTableSize      dd 0                  ; 4 bytes: Path Table Size (little-endian)
    .PVD_PathTableSizeBE    dd 0                  ; 4 bytes: Path Table Size (big-endian)
    .PVD_LocTypeLPathTable  dd 0                  ; 4 bytes: Location of Type L Path Table (little-endian)
    .PVD_LocOptionalTypeLPathTable dd 0           ; 4 bytes: Location of Optional Type L Path Table (little-endian)
    .PVD_LocTypeMPathTable  dd 0                  ; 4 bytes: Location of Type M Path Table (big-endian)
    .PVD_LocOptionalTypeMPathTable dd 0           ; 4 bytes: Location of Optional Type M Path Table (big-endian)
    .PVD_DirectoryEntry     db 34 dup(0)          ; 34 bytes: Directory Entry for Root Directory
    .PVD_VolumeSetIdentifier db 128 dup(0)        ; 128 bytes: Volume Set Identifier
    .PVD_PublisherIdentifier db 128 dup(0)        ; 128 bytes: Publisher Identifier
    .PVD_DataPreparerIdentifier db 128 dup(0)     ; 128 bytes: Data Preparer Identifier
    .PVD_ApplicationIdentifier db 128 dup(0)      ; 128 bytes: Application Identifier
    .PVD_CopyrightFileIdentifier db 37 dup(0)     ; 37 bytes: Copyright File Identifier
    .PVD_AbstractFileIdentifier db 37 dup(0)      ; 37 bytes: Abstract File Identifier
    .PVD_BibliographicFileIdentifier db 37 dup(0) ; 37 bytes: Bibliographic File Identifier
    .PVD_VolumeCreationDate db 17 dup(0)          ; 17 bytes: Volume Creation Date and Time
    .PVD_VolumeModificationDate db 17 dup(0)      ; 17 bytes: Volume Modification Date and Time
    .PVD_VolumeExpirationDate db 17 dup(0)        ; 17 bytes: Volume Expiration Date and Time
    .PVD_VolumeEffectiveDate db 17 dup(0)         ; 17 bytes: Volume Effective Date and Time
    .PVD_FileStructureVersion db 0                ; 1 byte: File Structure Version
    .PVD_Reserved1          db 1 dup(0)           ; 1 byte: Reserved Field
    .PVD_ApplicationUse     db 512 dup(0)         ; 512 bytes: Application Use
    .PVD_Reserved2          db 653 dup(0)         ; 653 bytes: Reserved for future standardization
    ; End of structure
    .PVD_End                db 0                  ; End marker (not part of the ISO 9660 standard, added for structure alignment)

actual_code_end:	; After this there is padding only

times 20480 - ($ - $$) db 0	; 20 KB padding
stage1_end:	; Ending with padding

Explanation:

1 Header:

BITS 16
ORG 0x7C00
  • BITS 16: Indicates that the code is written for 16-bit mode.
  • ORG 0x7C00: Specifies the origin address where the code will be loaded, which is 0x7C00. This is the conventional address where the BIOS loads the boot sector.

2 Entry Point:

stage1_start:
jmp main
  • The code execution starts here and jumps to the main label immediately.

3 Definitions:

%define STAGE2_AREA_SEGMENT 0x0000
%define STAGE2_AREA_OFFSET 0x0500

%define SUBSYSTEM_MEM_SEGEMENT 0x8000
%define SUBSYSTEM_MEM_OFFSET 0x00
%define FILE_LOADING_AREA_MEM_SEGMENT 0xCC00
%define FILE_LOADING_AREA_MEM_OFFSET 0x0000
  • Define constants for various memory areas used in the bootloader.

4 Main Function:

main:
    cli
    jmp 0x0:FixCS
  • cli: Disable interrupts to ensure safe execution.
  • jmp 0x0:FixCS: Far jump to FixCS to set up segment registers correctly.

5 Fix Segment Registers:

FixCS:
    xor ax, ax
    mov ds, ax
    mov es, ax

    mov ss, ax
    mov ax, 0x7C00
    mov sp, ax

    sti

    mov byte [bPhysicalDriveNum], dl

    call ClearScreenAndResetCursor
  • Zero out ax and use it to set ds, es, and ss to zero.
  • Set up the stack to start at 0x7C00.
  • Enable interrupts with sti.
  • Save the disk number from the dl register.
  • Clear the screen and reset the cursor.

6 Print Welcome Message:

    mov si, WelcomeToStage1
    call PrintString16BIOS
    call PrintNewline
  • Print a welcome message to the screen.

7 Calculate and Print Code Sizes

    mov ax, actual_code_end - stage1_start
    mov si, sActualStage1SizeStatement
    call PrintString16BIOS
    call PrintWordNumber
    call PrintNewline

    mov ax, stage1_end - stage1_start
    mov si, sPaddedStage1SizeStatement
    call PrintString16BIOS
    call PrintWordNumber
    call PrintNewline
  • Calculate and print the actual and padded sizes of the stage 1 bootloader code.

8 ISO 9660 Operations:

    call Read_volume_descriptors

    xor eax, eax
    mov ax, SUBSYSTEM_MEM_SEGEMENT
    mov es, ax

    mov si, SUBSYSTEM_MEM_OFFSET

    xor bx, bx
    mov bx, STAGE2_AREA_SEGMENT
    mov fs, bx

    mov di, STAGE2_AREA_OFFSET

    mov ax, Stage2FileIdentifier
    mov cx, Stage2FileIdentifierLength
    call Find_and_Load_File_from_Root

    jmp STAGE2_AREA_SEGMENT:STAGE2_AREA_OFFSET

    jmp $
  • Call Read_volume_descriptors to read ISO 9660 volume descriptors.
  • Set up segment and offset registers for loading the stage 2 file from the ISO filesystem.
  • Call Find_and_Load_File_from_Root to find and load the stage 2 bootloader.
  • Jump to the loaded stage 2 bootloader.
  • Infinite loop to prevent further execution if the jump fails.

9 Variables and Strings:

bPhysicalDriveNum db 0
WelcomeToStage1 db 'Welcome to the Stage1', 0
sPassedDriveNumber db 'Passed Drive Number from Stage1 : ', 0
sActualStage1SizeStatement db 'Actual size of the stage1 code (without padding in bytes): ', 0
sPaddedStage1SizeStatement db 'Padded size of the stage1 code (with padding in bytes): ', 0

SampleTextFileIdentifier: db 'AB.TXT', 0
SampleTextFileIdentifierLength equ $ - SampleTextFileIdentifier - 1

Stage2FileIdentifier: db 'STAGE2.BIN', 0
Stage2FileIdentifierLength equ $ - Stage2FileIdentifier - 1
  • Define various string literals and variables used in the bootloader.

10 Primary Volume Descriptor:

PrimaryVolumeDescriptor:
    .PVD_Type db 0
    .PVD_StandardIdentifier db 5 dup(0)
    .PVD_Version db 0
    .PVD_Unused1 db 1 dup(0)
    .PVD_SystemIdentifier db 32 dup(0)
    .PVD_VolumeIdentifier db 32 dup(0)
    .PVD_Unused2 db 8 dup(0)
    .PVD_VolumeSpaceSize dd 0
    .PVD_VolumeSpaceSizeBE dd 0
    .PVD_Unused3 db 32 dup(0)
    .PVD_VolumeSetSize dw 0
    .PVD_VolumeSetSizeBE dw 0
    .PVD_VolumeSequenceNumber dw 0
    .PVD_VolumeSequenceNumberBE dw 0
    .PVD_LogicalBlockSize dw 0
    .PVD_LogicalBlockSizeBE dw 0
    .PVD_PathTableSize dd 0
    .PVD_PathTableSizeBE dd 0
    .PVD_LocTypeLPathTable dd 0
    .PVD_LocOptionalTypeLPathTable dd 0
    .PVD_LocTypeMPathTable dd 0
    .PVD_LocOptionalTypeMPathTable dd 0
    .PVD_DirectoryEntry db 34 dup(0)
    .PVD_VolumeSetIdentifier db 128 dup(0)
    .PVD_PublisherIdentifier db 128 dup(0)
    .PVD_DataPreparerIdentifier db 128 dup(0)
    .PVD_ApplicationIdentifier db 128 dup(0)
    .PVD_CopyrightFileIdentifier db 37 dup(0)
    .PVD_AbstractFileIdentifier db 37 dup(0)
    .PVD_BibliographicFileIdentifier db 37 dup(0)
    .PVD_VolumeCreationDate db 17 dup(0)
    .PVD_VolumeModificationDate db 17 dup(0)
    .PVD_VolumeExpirationDate db 17 dup(0)
    .PVD_VolumeEffectiveDate db 17 dup(0)
    .PVD_FileStructureVersion db 0
    .PVD_Reserved1 db 1 dup(0)
    .PVD_ApplicationUse db 512 dup(0)
    .PVD_Reserved2 db 653 dup(0)
    .PVD_End db 0
  • Define the structure of the ISO 9660 Primary Volume Descriptor (PVD), used to store metadata about the volume.

11 Padding:

actual_code_end:

times 20480 - ($ - $$) db 0
stage1_end:
  • Add padding to ensure the bootloader is exactly 20KB in size. The times directive fills the remaining space with zeroes.

iso9660.inc:

%ifndef __ISO_9660_INC__
%define __ISO_9660_INC__


%define ROOT_DIRECTORY_ENTRY_LOCATION 0x90000	; It is the subsystem memory area


; **************************
; ReadVolumeDescriptor:
; Reads the LBA 16 of the ISO disk and checks, if it is Primary Volume Descriptor.
; -- If it is, then Proceed further by extracting the Root Directory Entry and
;    printing the root directory entries.
; -- If not the PVD, then Read the next LBA which is 17, until we have the PVD or
;    we encounter the Volume set terminator descriptor (which marks the end of the descriptors)
;
; IN:
; 	- Nothing
; OUT:
;	- Nothing
; **************************
Read_volume_descriptors:
	pushad 		; save the state
	mov si, sReadingVolumeDescriptorsStatement
	call PrintString16BIOS
	call PrintNewline
.iterate_descriptor:
     xor eax, eax	; clear out the eax
     mov esi, eax	; clear out the esi
     mov ax, 0x0000
     mov es, ax		; set es to 0x0000
     mov bx, PrimaryVolumeDescriptor;VOLUME_DESCRIPTOR_READ_LOCATION
     
     mov eax, [dwVolumeDescriptorStartingSector]	; starting sector low 32 bit (0-indexed LBA)
     mov esi, 0		; starting sector high 32 bit
     
     mov ecx, 1		; number of sectors to read
     mov edx, 2048	; Sector sizes in bytes (1 sector = 2048 in ISO 9660)
     call ReadFromDiskUsingExtendedBIOSFunction

     ; Verify the PVD identifier 'CD001',
     ; which would be at offset 1 of Volume Descriptor structure.
     mov si, PrimaryVolumeDescriptor.PVD_StandardIdentifier;VOLUME_DESCRIPTOR_READ_LOCATION + 1
     mov cx, 5		; 5 characters to check
     mov di, iso_id
     repe cmpsb
     jne .invalid_iso_disk

    ;; We got the valid iso disk identifier.
    ; Print valid iso disk statement.
	push si
	mov si, sValidISODiskIdentifierString
	call PrintString16BIOS
	call PrintNewline
	pop si


    ; Print the Volume Descriptor Type
	mov si, sVolumeDescriptorTypeStatement
	call PrintString16BIOS
	call PrintWordNumber
	call PrintNewline
 
    mov byte al, [PrimaryVolumeDescriptor.PVD_Type];[VOLUME_DESCRIPTOR_READ_LOCATION]
    ; Check if the descriptor is Primary Volume Descriptor.
    cmp al, 0x01	; Check for the Primary Volume Descriptor (PVD)
    jne .read_next_volume_descriptor	; If not PVD, read next descriptor
    
    ;; Got PVD
    ; Print the PVD statement
	mov si, sGotPVDStatement
	call PrintString16BIOS
	call PrintNewline

    ;; Read the Root Directory Entry from the PVD,
    ;; which is at offset 156.
    ;; Root Directory Entry is of 34 bytes.
;    mov si, VOLUME_DESCRIPTOR_READ_LOCATION
;    add si, 156		; Offset 156, where the Root Directory Entry Structure is located.
mov si, PrimaryVolumeDescriptor.PVD_DirectoryEntry
;    mov si, 0x809c	; si = 0x8000 + 156
    mov dword eax, es:[si + 2] ; Logical Block Address of the extent (first 4 bytes)
    xor edx, edx
    mov edx, eax		; Save LBA

    ;; Read the Root Directory Entry at Location 0x9000
    mov ax, SUBSYSTEM_MEM_SEGEMENT;0x9000;0x0000
    mov es, ax
    mov bx, SUBSYSTEM_MEM_OFFSET;0x00;ROOT_DIRECTORY_ENTRY_LOCATION ;0x9000
    
    mov eax, edx	; starting sector low 32 bit (0-indexed LBA)
    mov esi, 0		; starting sector high 32 bit
     
    mov ecx, 1		; number of sectors to read
    mov edx, 2048	; Sector sizes in bytes (1 sector = 2048 in ISO 9660)
    call ReadFromDiskUsingExtendedBIOSFunction

    ;; Read Root Directory Entry and Print its Entries Identifier.
    mov si, ROOT_DIRECTORY_ENTRY_LOCATION  ; 0x9000	; Memory Address where the Root Directory Entries (Record)
    			; is read.

    call Read_Root_Directory_Entry
   jmp .done_reading_volume_descriptor	; We are done reading and printing root directory entries.

;; Read the very next volume decriptor.
.read_next_volume_descriptor:
    cmp al, 0xFF			; Check for the end of volume descriptor list
    					; which is Volume Descriptor Set Terminator
    					; whose type (first byte) is 0xFF.
    je .volume_descriptor_terminator

    add dword [dwVolumeDescriptorStartingSector], 1	; read next sector i.e next volume descriptor.
    jmp .iterate_descriptor


;; Volume Descriptor Set Terminator
.volume_descriptor_terminator:
	mov si, volume_descriptor_terminator_encountered
	call PrintString16BIOS
	jmp .done_reading_volume_descriptor

.invalid_iso_disk:
	;; We got the Invalid ISO DISK
	; Print the invalid statement and go to infinite loop
	mov si, invalid_iso_disk_statement
	call PrintString16BIOS
	call PrintNewline

;;;TODO return the status, in case of failure as well as success.

.done_reading_volume_descriptor:
	popad		; restore the state
ret	; end of Read_volume_descriptors function.


; **************************
; Reads the Root Directory Entry which should be pointed
; by `SI`. It scans all the entries of the root directory
; and prints the identifier(name) of one and all.
; IN:
; 	- SI Root Directory Entry
; **************************
Read_Root_Directory_Entry:
	pushad		; save the state
.iterate_entry:
	xor ax, ax		; Clear out the ax register
	mov byte al, es:[si]	; it points to the 0 offset in directory entry.
				; At Offset 0 is length of the record.
				; It should be non zero, if zero means no valid record.
	test al, al
	
	jz .reading_done
	
	;; It is valid directory record.

	xor cx, cx
	xor dx, dx
	mov byte cl, es:[si + 32]	; get the file identifier length.
	mov byte dx, cx
	call PrintWordHex
	call PrintNewline
	mov di, si		; di and si both contains the current directory entry.
	add di, 33		; Add 33 to di which is the starting of
				; file identifier of the current directory entry.
.print_entries_identifier_char:
	mov byte al, es:[di]	; read the first character of current directory
				; entry's file identifier.
	call PrintChar16BIOS
	inc di			; jmp to next char in file identifier.
	loop .print_entries_identifier_char	; loop to print next char.
	call PrintNewline	; '\n'
	add byte si, es:[si]	; jump to next directory entry by adding
				; the length of the current directory entry.
	jmp .iterate_entry

.reading_done:
	popad 	; restore the state
ret


; **************************
; Find_and_Load_File_from_Root()
; Reads the Root Directory Entry which should be pointed by ES and SI, as
; SUBSYSTEM_MEM_SEGEMENT:SUBSYSTEM_MEM_OFFSET.
; Then scan for the file with identifier pointed by AX of length in BX.
; If found load it at location mentioned by FS and DI, and prints the content of 
; loaded file.
;
; IN:
;	- AX Address of File Identifier, the file to search for (in capital letters)
;
;	- ES Segment of Root Directory Entry
; 	- SI Root Directory Entry
;
;	- FS Segment of File Loading Address
;	- DI Offset of File Loading Address
;
; LOCAL VARIABLE:
;	VAR1 = [bp - 4] = Address of the Current Directory entry.
;	VAR2 = [bp - 8] = Found file LBA.
;	VAR3 = [bp - 12] = Sector rounded off file size.
;	VAR4 = [bp - 16] = Segment of Root Directory Entry.
;	VAR5 = [bp - 20] = Offset of Root Directory Entry.
;	VAR6 = [bp - 24] = Segment of File Read
;	VAR7 = [bp - 28] = Offset of File Read
;	VAR8 = [bp - 32] = File Identifier
;	VAR9 = [bp - 36] = File Identifier Length for comparison
; **************************
Find_and_Load_File_from_Root:
	pusha		; save the state
	push bp		; Save old base pointer
	mov bp, sp	; Set new base pointer
	sub sp, 36	; Allocate 36 bytes for local variables
			; 9 local variables of size 4 bytes each

;; Store parameters in local variables
	mov word [bp - 36], cx	; store the file identifier length
	mov word [bp - 32], ax	; store the file identifier address
	mov word [bp - 4], si	; store the address of first entry
				; of Root Directory Entries, it will be updated to
				; point to next entry during scanning.

	; Segment and Offset of the root directory record.
	mov word [bp - 16], es	; Segment of RDR (Root Directory Record)
	mov word [bp - 20], si	; Offset of RDR

	; Segment and Offset of the file loading area
	mov word [bp - 24], fs	; Segment of the File loading area
	mov word [bp - 28], di	; Offset of the File loading area


	; Print the function job message
	; SI - is needy for the function so push the initial state into the stack
	; and pop after printing the string. Thus storing the initial value.
	push si
	mov si, sFindAndLoadFileStatement
	call PrintString16BIOS
	call PrintNewline
	pop si

	;; set es and si to the Root Directory Record's segment and offset respectively.
	xor ax, ax
	mov word ax, [bp - 16]	; Segment of RDR
	mov es, ax
	mov word si, [bp - 20]	; Offset of RDR

.iterate_entry:

	xor ax, ax		; Clear out the ax register
	mov byte al, es:[si]	; it points to the 0 offset in directory entry.
				; At Offset 0 is length of the record.
				; It should be non zero, if zero means no valid record.
	test al, al
	jz .didnt_find		; Reached the end of the directory entry list
				; and didnt find the file

	;; It is valid directory record.

	; Get the File Flags field (offset 25 from the start of the entry).
	mov byte al, es:[si + 25]
	; Check if it's a directory
	test al, 0x02	; Check if bit 1 is set
	jnz .is_directory

	;; It is a file
	
	;; Check it's identifier.
	xor cx, cx	; clear out cx
	xor dx, dx	; clear out dx
	mov byte cl, es:[si + 32]	; get the file identifier length,
					; which is at offset 32 of directory_entry_record.
	mov byte dx, cx			; Store the identifier length
					; into the DX.

	;; Check the file identifier
	mov di, si	; DI and SI points to the Directory Entry Record
	add di, 33	; add offset 33, which is the start of the file identifier
			; DI, now points to the file identifier beginning.
	mov word cx, [bp - 36]	; length of the file identifier.
	;mov cx, 6	; The length of the file identifier.
	mov word si, [bp - 32]	; Load SI to the identifier of the required file.
	;lea si, [file_identifier]
	repe cmpsb	; Keep checking the SI and DI for the match.
			; if the length of the file identifier in both DI and SI matches,
			; then we have the required file, else jump to the next
			; directory entry record.
	jne .onto_next	; Jump to the next directory record if file identifier of
			; particular size mismatch

	;; Found the file

	mov si, [bp - 4]	; Get the Current Root Directory Record in si

.got_file:
	;; got the file
	; Print the message claiming that we found the file, you searched for.
	push si
	mov si, sFoundTheFile
	call PrintString16BIOS
	call PrintNewline
	pop si

	;; Location of the extent of the File
	; i.e the LBA of the data of the file.
	mov eax, es:[si + 2] ; Logical Block Address of the extent (first 4 bytes)

	;; Save LBA, in local variable
	;; Store File LBA in local variable BP - 8
	mov dword [bp - 8], eax		; Store the File LBA
					; to second local variable.

	; Save File Data Length in local variable
	xor eax, eax
	mov byte ax, es:[si+ 10]	; Data length of the file in LSB
				; It is present at offset 10 of Directory Entry Record.
				; It is of 4 byte in size
				; and data length is in bytes.
	mov dword [bp - 12], eax

	;; Prints the Data length
	; push si
	; mov si, sLengthOfFile
	; call PrintString16BIOS
	; call PrintWordNumber
	; call PrintNewline
	; pop si

	;; Update the es and bx for the segment and offset of the file loading area
	;	from the local variable.
	mov word ax, [bp - 24];0x0000	; Segment of the File Loading Area
	mov es, ax
	mov word bx, [bp - 28]; Offset for the File Loading Area ; 0xB000

	;; Roundoff the size to the 2048 which is the sector size.
	; i.e if the data length is less than 2048, then sector to load should be
	; 1 which is 2048 bytes
	; If the data length is more than 2048, 2049 for instance, one more than 2048
	; then the sector to load will be 2 = (2048*2)bytes.
	; Now eax, consists the rounded off value to sector size
	mov eax, [bp - 12]	; Actual data length of the file.
	add eax, 2047
	mov ecx, 2048
	div ecx		; division also affect the edx register.
			; so be careful, if you have stored the necessary
			; information in edx, it must have got wiped out.
	; move the sector count to ecx.
	mov ecx, eax

	mov eax, [bp - 8]	; starting sector low 32 bit (0-indexed LBA)
				; fetch from the second local variable.
	mov esi, 0	; starting sector high 32 bit
	;mov ecx, 1	; Here you can explicitly specify the sector count,
			; Otherwise we already calculated the rounded off
			; sector count to sector size based on the data length.
	mov edx, 2048	; Sector sizes in bytes (1 sector = 2048 in ISO 9660)
	call ReadFromDiskUsingExtendedBIOSFunction


	; Below code is if you are loading a text file then you can print its content.
	;; Tell user about displaying the content of the file.
	; mov si, sPrintingTheFileContent
	; call PrintString16BIOS
	; call PrintNewline

	; push ds		; store the ds state
	; mov ax, [bp - 24]	; FILE_LOADING_AREA_MEM_SEGMENT
	; mov ds, ax	; set the ds to segment because lodsb in PrintString16BIOS function
			; uses the ds:si pointed string to load in AL.
			; TODO: Can we use it as es:si, so that ds should be untouched.
	;; Print the contents of the file.
	; mov si, [bp - 28]; FILE_LOADING_AREA_MEM_OFFSET
					; Prints the data from the 
					; file loaded area.
	; call PrintString16BIOS
	; call PrintNewline
	; pop ds		; restore the ds state

	; We are done here reading the contents of the file.
	jmp .reading_done

.is_directory:
	; handle the directory, for the time being, just jump to next entry.
	; Maybe you can recursively search for the file in every directory.
	; Or you can search for particular directory.

;; Update the si to point to next entry.
.onto_next:
	; load the base address of current entry back to si
	mov word si, [bp - 4]

	add byte si, es:[si]	; increment si to point to next entry
				; Increment by adding the size of current entry.
				; at offset 0 of directory entry, we have the size
				; of each directory entry. we can get to the second
				; entry by adding the size of current entry to the
				; current entry address.
	mov word [bp - 4], si	; update the next entry address in the local
				; variable as well.
	jmp .iterate_entry	; onto the next entry.

;; Sorry but we didnt find your file.
.didnt_find:
	mov si, sDidntFindTheFile
	call PrintString16BIOS
	call PrintNewline

.reading_done:
	add sp, 36	; Clear local variables
	mov sp, bp	; Reset Stack pointer
	pop bp		; Restore old base pointer
	popa 	; restore the state
;; End of the Find_and_Load_File_from_Root function
ret



;; Data for the Find_and_Load_File_from_Root function
sLengthOfFileIdentifierStatement: db 'Length of the File Identifier is (in bytes): ', 0
sLengthOfFile: db 'Length of the File (in bytes): ', 0
sUnpaddedSizeStatement: db 'Un-Padded Size of Bootloader (bytes): ', 0
sFindAndLoadFileStatement: db '[Find_and_Load_File_from_Root] Finding and Loading the file from root directory...', 0
sFoundTheFile: db 'Found the file.', 0
sPrintingTheFileContent: db 'Printing the content of the file.', 0
sDidntFindTheFile: db 'Didnt find the file.', 0


dwVolumeDescriptorStartingSector dd 16	;; starting sector where the volume descriptor resides.

invalid_iso_disk_statement: db 'Invalid ISO disk identifier.', 0
volume_descriptor_terminator_encountered: db 'Volume Descriptor Set Terminator Encountered.', 0
sReadingVolumeDescriptorsStatement: db 'Reading Volume Descriptors...', 0
sValidISODiskIdentifierString: db 'It`s valid ISO Disk Identifier.', 0
sVolumeDescriptorTypeStatement: db 'Volume Descriptor Type = ', 0
sGotPVDStatement: db 'We got the PVD.', 0

iso_id db 'CD001'
%endif

Explanation:

1. Read_volume_descriptors

  • Purpose: Reads the volume descriptors from the ISO disk to find the primary volume descriptor (PVD).
  • Process:
    1. Initializes registers and saves the current state using pushad.
    2. Enters a loop (.iterate_descriptor) to read each volume descriptor starting at sector 16.
    3. Uses ReadFromDiskUsingExtendedBIOSFunction to read a sector into memory.
    4. Checks if the identifier at offset 1 matches 'CD001' to confirm it’s an ISO disk.
    5. If the volume descriptor type is not PVD (type 1), it checks for the volume descriptor set terminator (type 255).
    6. If PVD is found, reads the root directory entry and prints it using Read_Root_Directory_Entry.

2. Read_Root_Directory_Entry

  • Purpose: Reads and prints the entries in the root directory.
  • Process:
    1. Iterates through each directory entry starting at the memory location specified by ROOT_DIRECTORY_ENTRY_LOCATION.
    2. Checks the length of the record at offset 0 to ensure it is non-zero.
    3. If valid, prints the file identifier length and the identifier itself.
    4. Moves to the next entry by adding the length of the current entry to si.

3. Find_and_Load_File_from_Root

  • Purpose: Finds and loads a specific file from the root directory based on the file identifier.
  • Process:
    1. Saves the current state and allocates space for local variables.
    2. Initializes local variables with parameters like file identifier length, root directory entry location, and file loading address.
    3. Iterates through each directory entry to find the file.
    4. If a matching file identifier is found, calculates the logical block address (LBA) and loads the file into memory.
    5. Optionally, prints the contents of the loaded file.

Helper Functions and Data

  • PrintString16BIOS: Prints a string using BIOS interrupts.
  • PrintNewline: Prints a newline character.
  • PrintWordNumber and PrintChar16BIOS: Functions for printing numbers and characters.
  • ReadFromDiskUsingExtendedBIOSFunction: Reads sectors from the disk using BIOS interrupts.
  • Various Data Strings: Predefined messages and identifiers used for printing status and information.

Error Handling and Messages

  • If the ISO disk identifier is invalid, it prints an error message.
  • If it encounters the volume descriptor set terminator, it prints a corresponding message and stops reading further descriptors.
  • If the file is not found in the root directory, it prints a message indicating the file was not found.