Fatal: INT18: Boot failure?

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
Ziddia
Member
Member
Posts: 38
Joined: Sat Nov 05, 2011 6:28 pm

Fatal: INT18: Boot failure?

Post by Ziddia »

Hello,

I've been reading through a set of tutorials/theory behind a bootloader (I've misplaced the link, but I'll edit it in as soon as I find it). I've been trying to make my main bootloader (boot.bin, burnt to the MBR) call my second stage loader (boot2.bin, in the root directory). However, when I try to use it in VirtualBox, I receive the above error. I'm not great with BIOS interrupts, although I've tried looking this one up, so I turn to these forums.

For reference, I'm using MagicISO to create a bootable .iso file, NASM for the assembly, and VirtualBox for virtualization.

Code:

Stage one/main bootloader:

Code: Select all

; Note - directly ripped from the tutorials, redesign later

;*********************************************
;	Boot1.asm
;		- A Simple Bootloader
;
;	Operating Systems Development Series
;*********************************************

bits	16						; we are in 16 bit real mode

org	0						; we will set regisers later

start:	jmp	main					; jump to start of bootloader

;*********************************************
;	BIOS Parameter Block
;*********************************************

; BPB Begins 3 bytes from start. We do a far jump, which is 3 bytes in size.
; If you use a short jump, add a "nop" after it to offset the 3rd byte.

bpbOEM			db "Zid OS  "			; OEM identifier (Cannot exceed 8 bytes!)
bpbBytesPerSector:  	DW 512
bpbSectorsPerCluster: 	DB 1
bpbReservedSectors: 	DW 1
bpbNumberOfFATs: 	DB 2
bpbRootEntries: 	DW 224
bpbTotalSectors: 	DW 2880
bpbMedia: 		DB 0xf8  ;; 0xF1
bpbSectorsPerFAT: 	DW 9
bpbSectorsPerTrack: 	DW 18
bpbHeadsPerCylinder: 	DW 2
bpbHiddenSectors: 	DD 0
bpbTotalSectorsBig:     DD 0
bsDriveNumber: 	        DB 0
bsUnused: 		DB 0
bsExtBootSignature: 	DB 0x29
bsSerialNumber:	        DD 0xa0a1a2a3
bsVolumeLabel: 	        DB "ZID FLOPPY "
bsFileSystem: 	        DB "FAT12   "

;************************************************;
;	Prints a string
;	DS=>SI: 0 terminated string
;************************************************;
Print:
			lodsb				; load next byte from string from SI to AL
			or	al, al			; Does AL=0?
			jz	PrintDone		; Yep, null terminator found-bail out
			mov	ah, 0eh			; Nope-Print the character
			int	10h
			jmp	Print			; Repeat until null terminator found
	PrintDone:
			ret				; we are done, so return

;************************************************;
; Reads a series of sectors
; CX=>Number of sectors to read
; AX=>Starting sector
; ES:BX=>Buffer to read to
;************************************************;

ReadSectors:
     .MAIN:
          mov     di, 0x0005                          ; five retries for error
     .SECTORLOOP:
          push    ax
          push    bx
          push    cx
          call    LBACHS                              ; convert starting sector to CHS
          mov     ah, 0x02                            ; BIOS read sector
          mov     al, 0x01                            ; read one sector
          mov     ch, BYTE [absoluteTrack]            ; track
          mov     cl, BYTE [absoluteSector]           ; sector
          mov     dh, BYTE [absoluteHead]             ; head
          mov     dl, BYTE [bsDriveNumber]            ; drive
          int     0x13                                ; invoke BIOS
          jnc     .SUCCESS                            ; test for read error
          xor     ax, ax                              ; BIOS reset disk
          int     0x13                                ; invoke BIOS
          dec     di                                  ; decrement error counter
          pop     cx
          pop     bx
          pop     ax
          jnz     .SECTORLOOP                         ; attempt to read again
          int     0x18
     .SUCCESS:
          mov     si, msgProgress
          call    Print
          pop     cx
          pop     bx
          pop     ax
          add     bx, WORD [bpbBytesPerSector]        ; queue next buffer
          inc     ax                                  ; queue next sector
          loop    .MAIN                               ; read next sector
          ret

;************************************************;
; Convert CHS to LBA
; LBA = (cluster - 2) * sectors per cluster
;************************************************;

ClusterLBA:
          sub     ax, 0x0002                          ; zero base cluster number
          xor     cx, cx
          mov     cl, BYTE [bpbSectorsPerCluster]     ; convert byte to word
          mul     cx
          add     ax, WORD [datasector]               ; base data sector
          ret
     
;************************************************;
; Convert LBA to CHS
; AX=>LBA Address to convert
;
; absolute sector = (logical sector / sectors per track) + 1
; absolute head   = (logical sector / sectors per track) MOD number of heads
; absolute track  = logical sector / (sectors per track * number of heads)
;
;************************************************;

LBACHS:
          xor     dx, dx                              ; prepare dx:ax for operation
          div     WORD [bpbSectorsPerTrack]           ; calculate
          inc     dl                                  ; adjust for sector 0
          mov     BYTE [absoluteSector], dl
          xor     dx, dx                              ; prepare dx:ax for operation
          div     WORD [bpbHeadsPerCylinder]          ; calculate
          mov     BYTE [absoluteHead], dl
          mov     BYTE [absoluteTrack], al
          ret

;*********************************************
;	Bootloader Entry Point
;*********************************************

main:

     ;----------------------------------------------------
     ; code located at 0000:7C00, adjust segment registers
     ;----------------------------------------------------
     
          cli						; disable interrupts
          mov     ax, 0x07C0				; setup registers to point to our segment
          mov     ds, ax
          mov     es, ax
          mov     fs, ax
          mov     gs, ax

     ;----------------------------------------------------
     ; create stack
     ;----------------------------------------------------
     
          mov     ax, 0x0000				; set the stack
          mov     ss, ax
          mov     sp, 0xFFFF
          sti						; restore interrupts

     ;----------------------------------------------------
     ; Display loading message
     ;----------------------------------------------------
     
          mov     si, msgLoading
          call    Print
          
     ;----------------------------------------------------
     ; Load root directory table
     ;----------------------------------------------------

     LOAD_ROOT:
     
     ; compute size of root directory and store in "cx"
     
          xor     cx, cx
          xor     dx, dx
          mov     ax, 0x0020                           ; 32 byte directory entry
          mul     WORD [bpbRootEntries]                ; total size of directory
          div     WORD [bpbBytesPerSector]             ; sectors used by directory
          xchg    ax, cx
          
     ; compute location of root directory and store in "ax"
     
          mov     al, BYTE [bpbNumberOfFATs]            ; number of FATs
          mul     WORD [bpbSectorsPerFAT]               ; sectors used by FATs
          add     ax, WORD [bpbReservedSectors]         ; adjust for bootsector
          mov     WORD [datasector], ax                 ; base of root directory
          add     WORD [datasector], cx
          
     ; read root directory into memory (7C00:0200)
     
          mov     bx, 0x0200                            ; copy root dir above bootcode
          call    ReadSectors

     ;----------------------------------------------------
     ; Find stage 2
     ;----------------------------------------------------

     ; browse root directory for binary image
          mov     cx, WORD [bpbRootEntries]             ; load loop counter
          mov     di, 0x0200                            ; locate first root entry
     .LOOP:
          push    cx
          mov     cx, 0x000B                            ; eleven character name
          mov     si, ImageName                         ; image name to find
          push    di
     rep  cmpsb                                         ; test for entry match
          pop     di
          je      LOAD_FAT
          pop     cx
          add     di, 0x0020                            ; queue next directory entry
          loop    .LOOP
          jmp     FAILURE

     ;----------------------------------------------------
     ; Load FAT
     ;----------------------------------------------------

     LOAD_FAT:
     
     ; save starting cluster of boot image
     
          mov     si, msgCRLF
          call    Print
          mov     dx, WORD [di + 0x001A]
          mov     WORD [cluster], dx                  ; file's first cluster
          
     ; compute size of FAT and store in "cx"
     
          xor     ax, ax
          mov     al, BYTE [bpbNumberOfFATs]          ; number of FATs
          mul     WORD [bpbSectorsPerFAT]             ; sectors used by FATs
          mov     cx, ax

     ; compute location of FAT and store in "ax"

          mov     ax, WORD [bpbReservedSectors]       ; adjust for bootsector
          
     ; read FAT into memory (7C00:0200)

          mov     bx, 0x0200                          ; copy FAT above bootcode
          call    ReadSectors

     ; read image file into memory (0050:0000)
     
          mov     si, msgCRLF
          call    Print
          mov     ax, 0x0050
          mov     es, ax                              ; destination for image
          mov     bx, 0x0000                          ; destination for image
          push    bx

     ;----------------------------------------------------
     ; Load Stage 2
     ;----------------------------------------------------

     LOAD_IMAGE:
     
          mov     ax, WORD [cluster]                  ; cluster to read
          pop     bx                                  ; buffer to read into
          call    ClusterLBA                          ; convert cluster to LBA
          xor     cx, cx
          mov     cl, BYTE [bpbSectorsPerCluster]     ; sectors to read
          call    ReadSectors
          push    bx
          
     ; compute next cluster
     
          mov     ax, WORD [cluster]                  ; identify current cluster
          mov     cx, ax                              ; copy current cluster
          mov     dx, ax                              ; copy current cluster
          shr     dx, 0x0001                          ; divide by two
          add     cx, dx                              ; sum for (3/2)
          mov     bx, 0x0200                          ; location of FAT in memory
          add     bx, cx                              ; index into FAT
          mov     dx, WORD [bx]                       ; read two bytes from FAT
          test    ax, 0x0001
          jnz     .ODD_CLUSTER
          
     .EVEN_CLUSTER:
     
          and     dx, 0000111111111111b               ; take low twelve bits
         jmp     .DONE
         
     .ODD_CLUSTER:
     
          shr     dx, 0x0004                          ; take high twelve bits
          
     .DONE:
     
          mov     WORD [cluster], dx                  ; store new cluster
          cmp     dx, 0x0FF0                          ; test for end of file
          jb      LOAD_IMAGE
          
     DONE:
     
          mov     si, msgCRLF
          call    Print
          push    WORD 0x0050
          push    WORD 0x0000
          retf
          
     FAILURE:
     
          mov     si, msgFailure
          call    Print
          mov     ah, 0x00
          int     0x16                                ; await keypress
          int     0x19                                ; warm boot computer
     
     absoluteSector db 0x00
     absoluteHead   db 0x00
     absoluteTrack  db 0x00
     
     datasector  dw 0x0000
     cluster     dw 0x0000
     ImageName   db "BOOT2   BIN"
     msgLoading  db 0x0D, 0x0A, "Loading Boot Image ", 0x0D, 0x0A, 0x00
     msgCRLF     db 0x0D, 0x0A, 0x00
     msgProgress db ".", 0x00
     msgFailure  db 0x0D, 0x0A, "ERROR : Press Any Key to Reboot", 0x0A, 0x00
     
          TIMES 510-($-$$) DB 0
          DW 0xAA55
Stage 2:

Code: Select all

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; boot2.asm: Jumped to immediately by loader. Contains actual  ;
; booting stuff.                                               ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
BITS 16

ORG 0x0

jmp main

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Main boot method. Will both write to screen and execute      ;
; necessary functions.                                         ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
main:
	mov si, boot_msg
	call print_string
	call newline
	cli
	hlt

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Stage2 subroutines                                           ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Prints a string to the screen.                               ;
; Takes the value of SI to do this.                            ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
print_string:			; Routine: output string in SI to screen
	mov ah, 0Eh		; int 10h 'print char' function

.repeat:
	lodsb			; Get character from string
	cmp al, 0
	je .done		; If char is zero, end of string
	int 10h			; Otherwise, print it
	jmp .repeat

.done:
	ret

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Newline character.                                           ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
newline:
	push	ax
	mov	ax, 0E0Dh	; CR
     int	10h
     mov	al, 0Ah		; LF
     int	10h
	pop	ax
     ret

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Sets up the A20 line for up to 4GB of memory.                ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
enable_a20:
	cli                ;Disables interrupts
	push	ax         ;Saves AX
	mov	al, 0xdd  ;Look at the command list 
	out	0x64, al   ;Command Register 
	pop	ax          ;Restore's AX
	sti                ;Enables interrupts
	mov si, a20_msg
	call print_string
	call newline
	ret 

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Hardcoded declarations.                                      ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
	boot_msg db 'Booting OS.', 0 ; Boot message
	a20_msg db 'A20 Line enabled for 4GB of memory', 0
Thankyou to anyone who can help - my bootloader was running fine before, and I'm stumped, as searching for the interrupt has turned up nothing of relevance to my problem. I was thinking that maybe the ISO turned out by MagicISO wasn't compatible with the FAT12 format in the stage one bootloader, but I can't see how that would trip the interrupt.

Ziddia

EDIT: Wow, formatting was lost between wordpad and the forum. Sorry about that, comments look a little funny.
Rudster816
Member
Member
Posts: 141
Joined: Thu Jun 17, 2010 2:36 am

Re: Fatal: INT18: Boot failure?

Post by Rudster816 »

CD's have a sector size of 2048, so padding it to 512 won't work. You'll need to put it on a HDD to test it properly.

Also, the first line needs to be either

Code: Select all

jmp short main
nop
or

Code: Select all

jmp near main
NASM is probably doing a short jump by default which will screw up the alignment. You could just add a nop to the end and assume the jump is short, but since your main label is so far down, you should explicitly state it's a short so NASM will throw you an error if it's too far down and you can correct it.
Ziddia
Member
Member
Posts: 38
Joined: Sat Nov 05, 2011 6:28 pm

Re: Fatal: INT18: Boot failure?

Post by Ziddia »

Thanks. I'm away from the computer for a while now, but I'll try and report back on how it goes.

I'm hoping that MagicISO can create bootable HDDs. Also, would you know why it was working earlier with padding to 512 (or does that not matter as much as I thought it did)?
User avatar
bubach
Member
Member
Posts: 1223
Joined: Sat Oct 23, 2004 11:00 pm
Location: Sweden
Contact:

Re: Fatal: INT18: Boot failure?

Post by bubach »

That's a bootsector made for floppy disks/images and FAT12. Could possibly be used on HDD (images) with FAT12 too, but the BIOS Parameter Block values would need to be changed accordingly. For CD-boot with ISO9660 as filesystem check out this:
http://bos.asmhackers.net/docs/booting/cd_boot/
"Simplicity is the ultimate sophistication."
http://bos.asmhackers.net/ - GitHub
User avatar
Combuster
Member
Member
Posts: 9301
Joined: Wed Oct 18, 2006 3:45 am
Libera.chat IRC: [com]buster
Location: On the balcony, where I can actually keep 1½m distance
Contact:

Re: Fatal: INT18: Boot failure?

Post by Combuster »

In general, using an bootloader designed for floppies does not work on other media. Virtualbox should support floppies - use that. Making an ISO image in the process only adds more causes for errors.
"Certainly avoid yourself. He is a newbie and might not realize it. You'll hate his code deeply a few years down the road." - Sortie
[ My OS ] [ VDisk/SFS ]
Ziddia
Member
Member
Posts: 38
Joined: Sat Nov 05, 2011 6:28 pm

Re: Fatal: INT18: Boot failure?

Post by Ziddia »

bubach wrote:That's a bootsector made for floppy disks/images and FAT12. Could possibly be used on HDD (images) with FAT12 too, but the BIOS Parameter Block values would need to be changed accordingly. For CD-boot with ISO9660 as filesystem check out this:
http://bos.asmhackers.net/docs/booting/cd_boot/
I'm definitely leaning towards the CD boot. Thankyou for your help!
Ziddia
Member
Member
Posts: 38
Joined: Sat Nov 05, 2011 6:28 pm

Re: Fatal: INT18: Boot failure?

Post by Ziddia »

bubach wrote:That's a bootsector made for floppy disks/images and FAT12. Could possibly be used on HDD (images) with FAT12 too, but the BIOS Parameter Block values would need to be changed accordingly. For CD-boot with ISO9660 as filesystem check out this:
http://bos.asmhackers.net/docs/booting/cd_boot/
What format is this file written in: http://bos.asmhackers.net/docs/booting/ ... 9660fs.inc ?

It's required by the bootloader, but it throws a lot of errors. Is it still compiled in NASM?
Ziddia
Member
Member
Posts: 38
Joined: Sat Nov 05, 2011 6:28 pm

Re: Fatal: INT18: Boot failure?

Post by Ziddia »

Again, nevermind, I think I figured it out.
Ziddia
Member
Member
Posts: 38
Joined: Sat Nov 05, 2011 6:28 pm

Re: Fatal: INT18: Boot failure?

Post by Ziddia »

Ziddia wrote:Again, nevermind, I think I figured it out.
...or not. It appears that my bootloader isn't able to read the second stage from the disc.

I borrowed the code temporarily from the website I was shown earlier, although I plan to rewrite it later. The bootloader complains that the OS-Loader can't be found.

Here's the bootloader code:

Code: Select all

;NOTE: Rewrite later, basically copied from elsewhere
org 0x7C00

%include "iso9660fs.inc"

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Bootloader entry point.                                      ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
start:
	cli

	xor ax,ax
	mov ds,ax					;set ds 2 0h
	mov sp,ax

	mov ax,9000h
	mov ss,ax					;set stack 2 90000h

	mov ax,1000h
	mov es,ax					;set es 2 10000h

	sti

	mov byte[bootdrv],dl		;save bootdrive

	call load_vol_desc
	test ax,ax
	jz .err_read

	call load_root_dir
	test ax,ax
	jz .err_read

	call load_loader
	test ax,ax
	jz .err_no_loader

	mov dl,byte[bootdrv]		;move bootdrive into dl for the loader

	jmp 1000h:0000h
;----------------------------
.err_read:
	mov si,msg_err_read
	call print

	jmp reboot
;----------------------------
.err_no_loader:
	mov si,msg_err_loader
	call print

	jmp reboot
;----------------------------

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Reboots the system.                                          ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
reboot:
	mov si,msg_reboot
	call print

	xor ax,ax
	int 16h
	int 19h
;----------------------------

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Prints a string to the screen (stored in si).                ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
print:
	pusha

	mov ah,0eh

.loop:
	lodsb
	test al,al
	jz .end
	int 10h
	jmp .loop

.end:
	popa
	ret
;----------------------------

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Loads volume data.                                           ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
load_vol_desc:

.loop:
	mov si,dap
	mov ah,42h
	mov dl,[bootdrv]
	int 13h						;load the lba which stands in the dap into the location which stands also in the dap

	jc .end_err

	cmp byte[es:0],1
	je .end						;is this the primary volume descriptor, if yes jump
	cmp byte[es:0],0ffh
	je .end_err					;is this the last volume descriptor, if yes jump

	inc dword[dap.lba]			;next lba
	jmp .loop

.end:
	mov ax,1
	ret

.end_err:
	xor ax,ax
	ret
;----------------------------

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Loads the root directory.                                    ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
load_root_dir:
	mov si,iso9660vol_desc.root_dir_rec

	mov eax,dword[es:si+iso9660dir_desc.loc_data]	;the start lba of the root directory
	mov ecx,dword[es:si+iso9660dir_desc.data_len]	;the length of the root directory
	shr ecx,11										;length of root dir / 2048, because we need the # of blocks
	add cx,1
	call load_lba

.end:
	ret
;----------------------------

;----------------------------
load_loader:
	xor si,si
	shl ecx,11					;in ecx is the # of blocks of the root dir, but we need the size

.loop_search:
	cmp byte[es:si],0
	je .end_err					;is this no root dir entry, if yes jump
	cmp si,cx
	je .end_err					;is si = size of root dir, if yes jump

	mov di,si
	add di,iso9660dir_desc.file_ident				;move the addr of the act entry into di and let it point to the file name

	push cx
	push si

	movzx cx,byte[es:si+iso9660dir_desc.len_file_ident]			;get the size of the file indentifier
	mov si,osloader_img
	rep cmpsb

	mov al,[si]					;when the strings were equal al should be 0

	pop si
	pop cx

	test al,al
	jz .load

	movzx ax,byte[es:si+iso9660dir_desc.len_dir_rec]
	add si,ax					;get size of the act entry and add it to si, so that si points to the next entry

	jmp .loop_search

.load:
	mov eax,dword[es:si+iso9660dir_desc.loc_data]	;start lba of the file
	mov ecx,dword[es:si+iso9660dir_desc.data_len]	;length of the file
	shr ecx,11
	inc cx											;we need the blocks 2 load for the file and 2 be sure that we load the whole file we inc cx, cause who cares if we load one more block than the file is big?!
	call load_lba

.end:
	ret

.end_err:
	xor ax,ax
	ret
;----------------------------

;----------------------------
;	Input:
;	EAX - LBA
;	CX - # of lbas 2 load
load_lba:
	pusha

	mov [dap.blocks],cx			;save # of blocks 2 load
	mov [dap.lba],eax			;save lba to load

	mov si,dap
	mov ah,42h
	mov dl,[bootdrv]
	int 13h

	jc .end_err

.end:
	popa
	mov ax,1
	ret

.end_err:
	popa
	xor ax,ax
	ret
;----------------------------

align 4
;----------------------------
;	data

;	vars
dap:
	.size		db 10h
	.reserved	db 0
	.blocks		dw 1
	.offset		dw 0
	.segment	dw 1000h
	.lba		dd 10h,0
bootdrv			db 0

;	consts
osloader_img	db 'boot2.bin',13,10,0

;	msgs
msg_reboot		db 'Press any key to reboot',13,10,0
msg_err_read	db 'error occured while reading disk',13,10,0
msg_err_loader	db 'OS-Loader not found',13,10,0
msg_loading db 'Preparing to load file...',13,10,0

times 510-($-$$) db 0
dw 0aa55h
I'm pretty sure that boot2.bin is the wrong way to try and read it, but I can't figure out what the correct name would be.

Thankyou to anyone who can help.
User avatar
brain
Member
Member
Posts: 234
Joined: Thu Nov 05, 2009 5:04 pm
Location: UK
Contact:

Re: Fatal: INT18: Boot failure?

Post by brain »

It should be ok but you have linefeeds on the filename, 13, 10, Try removing them and see if it works, iso9660 does not terminate filenames with newlines and it looks like you check the string till you reach 0x00.

Edit: you also have not accounted for the revision number after the name, separated from the name with ; - maybe you need to read the iso9660 spec and actually understand the code you are borrowing.
see here for iso9660 code in c which you will have to adapt to assembler so it isn't just straight copy and paste.
User avatar
bubach
Member
Member
Posts: 1223
Joined: Sat Oct 23, 2004 11:00 pm
Location: Sweden
Contact:

Re: Fatal: INT18: Boot failure?

Post by bubach »

That's not my code and I have never verified that it works, but after doing some googling it seems that file names can be of variable size and end with ";1" for file ID one. Didn't look into it that much, but for a single file in the root dir I guess you can assume it's ID 1.

So, db "boot2.bin;1",0 might do the trick. Also you should try and google ISO9660 for more information and code examples, here's another take at a cd bootsector:
http://code.google.com/p/reindeeros/sou ... rOS%2Fboot
"Simplicity is the ultimate sophistication."
http://bos.asmhackers.net/ - GitHub
User avatar
brain
Member
Member
Posts: 234
Joined: Thu Nov 05, 2009 5:04 pm
Location: UK
Contact:

Re: Fatal: INT18: Boot failure?

Post by brain »

Names will always be uppercase and the version almost always ;1 so yeah almost right, its definitely important to 1) read the spec and 2) look at an iso image in a hex editor.
Ziddia
Member
Member
Posts: 38
Joined: Sat Nov 05, 2011 6:28 pm

Re: Fatal: INT18: Boot failure?

Post by Ziddia »

Thankyou to everyone - I'll be trying to fix it now, I'll see if it works. I'm also reading through the iso9660 specifications, so I don't mes up on something silly like this again.
Post Reply