flat assembler
Message board for the users of flat assembler.

Index > OS Construction > Fat12 Boot Loader help...

Author
Thread Post new topic Reply to topic
xleelz



Joined: 12 Mar 2011
Posts: 86
Location: In Google Code Server... waiting for someone to download me
xleelz 12 Sep 2011, 22:23
I was reading Broken Thorn for FAT12 bootloader and copied the code to see if I could figure it out, but every time I run it in VB it does fine for a while then says "FATAL: INT18: BOOT FAILURE"


here's the code for it:
Code:
use16
org 0

jmp boot
nop

BPB:
OemName                    db "ABloader"
BytesPerSector               dw 512
SectorsPerCluster     db 1
ReservedSectors         dw 1
NumberofFats            db 2
RootEntries             dw 224
TotalSectors          dw 2880
Media                        db 0xF0
SectorsPerFat                dw 9
SectorsPerTrack         dw 18
HeadsPerCylinder       dw 2
HiddenSectors           dd 0
TotalBigSectors         dd 0
DriveNumber             db 0
Unused                  db 0
BootSignature           db 0x29
SerialNumber         dd 0x12345678
VolumeLabel            db "TEST OS    "
FileSystem                db "FAT12   "

boot:
    cli
 mov ax,0x07C0
       mov ds,ax
   mov es,ax
   mov fs,ax
   mov gs,ax

       mov ax,0x0000
       mov ss,ax
   mov sp,0xFFFF
       sti

     mov si,msgloading
   call print
  mov byte [DriveNumber], dl

loadRoot:

;find the size of root dir       
    xor cx,cx
   xor dx,dx
   mov ax,0x0020                   ;32 byte directory entry
    mul word [RootEntries]          ;Multiply by number of root entries
 div word [BytesPerSector]       
    xchg ax,cx
  
;lets try to find the start of the root dir now...

  mov al, byte [NumberofFats]
 mul word [SectorsPerFat]
    add ax, word [ReservedSectors]
      mov word [datasector],ax        
    add word [datasector], cx       

;Now let's finally read it into memory... at 7C00:0200

     mov bx, 0x0200
      call readSectors

;lets find our kernel file Very Happy
   mov cx, word [RootEntries]
  mov di,0x0200
.loopr:
        push cx
     mov cx, 0x000B          ;Eleven character name Razz
       mov si, KernName
    push di                 ;Save position of di...
     rep cmpsb
   pop di                  ;Restore starting position
  je loadFat              ;If it was the right name, load it!
 pop cx                  ;Restore cx
 add di, 0x0020          ;Up the memory location to the next entry
   loop .loopr
 jmp failure             ;we're a failure if it comes to this :'(

loadFat:
      
;save starting cluster of boot image

        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 [NumberofFats]
 mul word [SectorsPerFat]
    mov cx, ax
  
;compute location of FAT and store in ax

    mov ax, word [ReservedSectors]

;read FAT into memory (7C00:0200)

     mov bx, 0x0200
      call readSectors

; read image file into memory (0050:0000)

   mov ax, 0x0050
      mov es, ax
  mov bx, 0x0000
      push bx

loadImage:
       
    mov ax, word [cluster]
      pop bx
      call C2LBA
  xor cx,cx
   mov cl, byte [SectorsPerCluster]
    call readSectors
    push bx

;compute next cluster

    mov ax, word [cluster]
      mov cx, ax
  mov dx, ax
  shr dx, 0x0001
      add cx, dx
  mov bx, 0x0200
      add bx, cx
  mov dx, word [bx]
   test ax, 0x0001
     jnz .odd
.even:
      
    and dx, 0000111111111111b
   jmp .done
.odd:
      shr dx, 0x0004

.done:
    mov word [cluster], dx
      cmp dx, 0x0FF0
      jb loadImage
done:
   mov si, msgcrlf
     call print
  push word 0x0050
    push word 0x0000
    retf
failure:
        mov si, msgfailure
  call print
  mov ah, 0x00
        int 16h
     int 19h


;=======================================================
;FUNCTIONS GO HERE
;-------------------------------------------------------

print:
     lodsb
       or al,al
    jz .pdone
   mov ah,0eh
  int 10h
     jmp print
.pdone:
    ret

readSectors:
 mov di, 0x0005          ;Five retires for error
.loopr:
      push ax
     push bx
     push cx
     call LBA2CHS
        mov ah, 0x02
        mov al, 0x01
        mov ch, byte [absoluteTrack]
        mov cl, byte [absoluteSector]
       mov dh, byte [absoluteHead]
 mov dl, byte [DriveNumber]
  int 13h
     jnc .success
        xor ax,ax
   int 13h
     dec di
      pop cx
      pop bx
      pop ax
      jnz .loopr
  int 18h
.success:
    mov si, msgprogress
 call print
  pop cx
      pop bx
      pop ax
      add bx, word [BytesPerSector]
       inc ax
      loop readSectors
    ret
;************************************
;CHS TO LBA conversion
; LBA = (cluster - 2) * sectors per cluster
;**************************************
C2LBA:
      sub ax,0x0002
       xor cx,cx
   mov cl, byte [SectorsPerCluster]
    mul cx
      add ax, word [datasector]
   ret

;*********************************
;LBA to CHS
; 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)
;*********************************

LBA2CHS:
   xor dx,dx
   div word [SectorsPerTrack]
  inc dl
      mov byte [absoluteSector], dl
       xor dx,dx
   div word [HeadsPerCylinder]
 mov byte [absoluteHead], dl
 mov byte [absoluteTrack], al
        ret

absoluteSector db 0x00
absoluteHead db 0x00
absoluteTrack db 0x00

datasector dw 0x0000
cluster dw 0x0000
KernName db "KERN    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 0AA55h
    


any ideas what went wrong?

_________________
The person you don't know is the person that could help you the most... or rape you, whichever they prefer.
Post 12 Sep 2011, 22:23
View user's profile Send private message Reply with quote
lagg070988



Joined: 09 Jul 2011
Posts: 5
lagg070988 13 Sep 2011, 02:38
"FATAL: INT18: BOOT FAILURE"
this interrupt is called when there is no bootable disk available to the system...
so, i think that you are trying to boot a disk that the bios don't have detected as bootable...
take a look in your bios Smile
Post 13 Sep 2011, 02:38
View user's profile Send private message MSN Messenger Reply with quote
me239



Joined: 06 Jan 2011
Posts: 200
me239 13 Sep 2011, 04:39
here, my code is based of his code, but I used empirical numbers instead of calculating them to save space. Also, maybe a stupid question, are you sure the file is on the floppy and named correctly?
Code:
;This bootsector was created by ME239 and is protected under the GNU license agreement.
;This article was intended for educational purposes and was optimized for readability and size.
;The numbers used for the sectors and number of sectors is written in an emperical way to save on
;space, but full equations are given in the comments
; THIS MUST BE COMPILED WITH FASM!
org 0 ; we start everything at zero
jmp start        ; the jump must be 3 bytes before the BPB. A jump is 2 bytes so we add a NOP, or 1 byte
nop              ; This is just the BPB
OEM  db 'SAMPLEBT' ; the name of our disk
BytesPerSecot dw 512
SectorsPerCluster db 1
ReservedSectors dw 1
NumberofFATs db 2
RootEntries dw 224
TotalSectors dw 2880
Media db 0xf8 ; what are we? A floppy, HD, etc.
SectorsPerFAT dw 9
SectorsPerTrack dw 18
HeadsPerCylinder dw 2
dd 0 ; These are hidden sectors, but we won't use them
dd 0
DriveNumber db 0      ;here is the start of the extended BPB (for DOs and windwos)
Unused db 0
Bootsig db 29h
Serial dd 0x1a2a3a
VolumeLabel db 'SAMPLEBOOT '
FileSystem db 'FAT12   '
start:
        cli     ; let's disable interrupts while we configure the stack and segments
        mov     ax, 0x07c0 ; look at an explanation of segmented memory (at the bottom)_
        mov     es, ax  ; let's set all the registers to the new segment
        mov     ds, ax
        mov     gs, ax
        mov     fs, ax
        xor     ax, ax
        mov     ss, ax ; stack segment is now 0
        mov     sp, 0ffffh ; but the stack pointer is at 0xffff giving us a 65,535 byte stack
        sti     ; we're done here, let's re-enable interrupts
        mov     ax, 19 ; Root directory starts at 19 (look at FAT12 map for help)\
        mov     cx, 14 ; Root directory size (224 entries * 32 bytes per entry all divided by 512(sectors per byte)
        mov     bx, 200h ; we want to read the root directory to the end of the bootloader (200h = 512 decimal)
        call    readsectors ; put the sectors into RAM
        mov     di, 0x200 ; set the data index to 200h
        mov     cx, 224 ; max number of root entries so we don't read over the limit
findfile: ; let's find our kernel!
        push    cx ; save cx
        mov     cx, 11 ; each entry in FAT12 has an 11 byte name
        mov     si, filen ; the name of our kernel
        push    di ; save the data index
        repe    cmpsb ; let's compare
        pop     di ; restore DI
        je      filefound ; was it equal? If so, then we found our file
        pop     cx ; restore CX
        add     di, 32 ; let's search the next entry
        loop    findfile ; loop this only 224. If the file isn't found, then fail
        int     18h ; file wasn't found, let's bail!
filefound: ; we've found our kernel! Now let's load it!
        pop     cx ; let's restore CX to keep the stack intact
        mov     dx, word[di+1ah] ; each FAT12 entry contains the first cluster 26 bytes after the beginning of the entry (0x1a = 26 decimal)
        mov     word[cluster], dx ; let's save this for later
        mov     ax, 1 ; there is one reserved sector on our disk, the bootloader. So that means the FAT table is right after it!
        mov     cx, 9 ; there are to FAT tables. Each are 9 sectors and identical stored only as backups to eachother. So let's just load the first one
        mov     bx, 0x200 ; let's overwrite the root directory since we already have the first cluster
        call    readsectors ; let's read the FAT table into RAM
        mov     ax, 0x60 ; this is our new segment where we want to load the kernel
        mov     es, ax ; let's put that into the ES register
        xor     bx, bx ; zero out BX so the kernel will be loaded to 0060:0000 (ES:BX)
        push    bx ; save BX for the loop
clusterloop:
        mov     ax, word[cluster] ; put the cluster number in AX
        sub     ax, 2 ; the conversion for cluster to LBA (or Logical Sector) is simply (cluster number - 2)* the number of sectors per cluster (we're a floppy so we only have one sector per cluster)
        add     ax, 33 ; the data portion starts at 33. (1 reserved sector + 2 FAT tables * 9 sectors each)+((224 root entries * 32 bytes per entry)/512 bytes per sector) = 33
        mov     cx, 1 ; we only have one sector per cluster, so we only read one sector
        pop     bx
        call    readsectors
        push    bx ; save BX so it doesn't get destroyed
        mov     ax, word[cluster] ; load AX with the cluster number
        mov     dx, ax
        mov     cx, ax ; let's do the same with DX and CX
        shr     dx, 1 ; divide DX by two
        add     cx, dx ; add DX back to CX so we now have 3/2 of the original cluster
        mov     bx, 0x200 ; move the FAT table into BX
        add     bx, cx ; BX = the new cluster number
        mov     dx, word[bx] ; put the new cluster number in DX
        test    ax, 1 ; tests the last cluster number to see if it is odd or even (all odd numbers have bit 1 enable, hence the test 1)
        jnz     odd_cluster ; the cluster was odd, so let's take care of it
        and     dx, 0fffh ; let's take the low 12 bits of the new cluster (12 bits, get it? FAT12, 12 bits per cluster number!)
        jmp     done ; let's jump over the odd_cluster routine
odd_cluster:
        shr     dx, 4 ; let's take the high twelve bytes excluding the low 4
done:
        mov     word[cluster], dx ; let's save our new cluster
        cmp     dx, 0ff0h ; the number 0ff0h (or 4080 decimal) marks the end of a cluster chain, meaning we have finished reading the file!
        jb      clusterloop ; was it below 0xff0? If so let's keep reading
        mov     ax, es ; COM files are loaded at offset 0x100, so let's fix the memory (look at the bottom of the article for a better explanation)
        sub     ax, 10h
        mov     es, ax
        mov     ds, ax
        mov     ss, ax
        xor     sp, sp
        push    es
        push    100h
        retf    ; we've loaded our kernel, so let's execute it!
readsectors: ; our loop for reading the disk into RAM
        mov     di, 5 ; let's give it only 5 tries before quitting
sectloop:
        push    ax ; let's save our registers!
        push    bx
        push    cx
        push    dx
        call    lbachs ; we can't use logical sectors, so we must convert is to Cylinder, Head, and Sector
        mov     ah, 02h ; BIOS disk read funtion
        mov     al, 1 ; read only one sector
        mov     dl, 0 ; we're a floppy, so we are the first disk
        mov     dh, [head]
        mov     cl, [sector]
        mov     ch, [track]
        int     13h ; read it!
        jnc     success ; was there an error? If not, jump to the next routine
        xor     ax, ax ; BIOS disk reset function
        int     13h
        pop     dx ; restore the registers
        pop     cx
        pop     bx
        pop     ax
        dec     di ; decrement DI
        jnz     sectloop ; keep going until we reach five
        int     18h ; let's bail
success:
        pop     dx ; restore our registers
        pop     cx
        pop     bx
        pop     ax
        inc     ax ; let's read the next sector
        add     bx, 512 ; there 512 bytes per sector, so let's update BX (our buffer)
        loop    readsectors ; remember, CX = number of sectors to read
        ret ; we read everything without a problem, so let's return
lbachs: ; Sector = LBA MOD SectorsPerTrack (1Cool
        ; Head = (LBA/SectorsPerTrack) MOD HeadsPerCylinder (2)
        ; Track(/Cylinder) = (LBA/SectorsPerTracl) / HeadsPerCylinder (2)
        pusha ; shortcut to save all registers
        xor   dx, dx ; since this is fixed point math, all remainders of divisions are stored in DX, so let's zero DX
        mov   cx, 18 ; SectorsPerTrack
        div   cx ; divide AX (LBA) by the
        inc   dl ; in reality the number of the first sector is 0, but BIOS funtion only accepts 1 as the first sector
        mov   byte[sector], dl ; save our sector
        mov   cx, 2 ; HeadsPerCylinder
        xor   dx, dx ; let's zero out DX again
        div   cx
        mov   byte[head], dl ; let's save the rest
        mov   byte[track], al
        popa ; restore our registers
        ret ; return
cluster dw  0 ; variable for our current cluster
sector  db  0 ; variables for CHS
head    db  0
track   db  0
filen   db  'KERNEL  COM' ; 11 byte file name, CAPITALIZED! 8 bytes for the file name, 3 bytes for the extension
times 510-($-$$) db 0 ; fill in the remaining space with zero
dw 0xaa55 ; legacy boot signature
;*****************NOTES************************
;Here is a quick lesson in how segmented memory works.
;The layout goes like this SEGMENT:OFFSET. Basically, each segment is a place in memory and the offset is a more detailed spot.
;Now you may have realized that I used segment 7c0h rather than 7c00h. Now here is why, each segment is 0x10 (or 16 decimal) times as large as a single offset;
;therefore, the same location can be accessed at both 07c0:0000 or 0000:7c00. Now this also brings us to the explanation for the COM file execution. I subtracted
;0x10 from the segment, so this equal to setting the offset to 0x100. Then all the segments were set to the new segment along with the stack.
;
;Now here is map of how the FAT12 system is laid out
;|----------------------------------------------------------------------|
;|BootSector| FAT table 1| FAT table 2 | Root Directory| Data Region    |
;|512 bytes | 4,608 bytes| 4,608 bytes |  7,168 bytes  | 1,457,664 bytes|
;|1 sector  | 9 sectors  | 9 sectors   |  14 sectors   |  2,847 sectors |
;|______________________________________________________________________|
;
;Here is an explanation of what clusters are.
;A cluster is simply the number (-2) of sectors after the Root Directory the data is located at.
;So it is really just a sector number. So then you ask, "If it's only one sector, then why don't they just call it a sector?".
;The answer to that question is that other larger FAT systems (FAT16, FAT32) use clusters that can larger than 1 sector at a time;
;therefore, we call it a cluster just because it is universal.
;
;Now here is a breif explantion of how the FAT12 table works.
;In the FAT12 system, the FAT table is comprised of numbers containing the next cluster
;in a file's chain. That's simple enough, now it's interpretting those numbers where it
;becomes confusing. The first cluster available on a disk is 2. So let's say our directory
;entry says it's first cluster is 2. OK, let's go read our table. To retrieve the number of our next cluster,
;we get 3/2 of our current cluster. So let's get 3/2 of 2 and now we have 3. Now we get the word at that offset
;in the FAT table. Good, now we are close to having the next sector! All that's left is to test and see if is was odd (since 3/2 of an odd number is a fraction).
;To do that we use the TEST instruction. Testing AX (assuming that AX contains the last cluster) with 1 tests bit 1 to see if it is enabled. If bit 1 is enabled,
;the number is odd otherwise it is even. To adjust the cluster if it is odd, we take the high 12 bits of the word. To do this we shift the new cluster over 4 places
;(1111111111110000b becomes 0000111111111111b). The instruction SHR means shift right, so shifting right four times is equivalent to dividing by 16 (2^4, this unrelated, but
;interesting). OK, so what if it's even? Then we take the low 12 bits. To do this we use the AND instruction as a filter. In the code I use 0xfff to filter it (0xfff =
; 000011111111111b). So now that we have the correct cluster, we repeat the previous steps with the new cluster until you reach 0ff0h, which means the end of a file's
;cluster chain.
    
Post 13 Sep 2011, 04:39
View user's profile Send private message Reply with quote
me239



Joined: 06 Jan 2011
Posts: 200
me239 13 Sep 2011, 04:57
Here, I modified your code so it now executes a COM file under the name KERN.COM
Code:
use16
org 0

jmp boot
nop

BPB:
OemName                 db "ABloader"
BytesPerSector          dw 512
SectorsPerCluster       db 1
ReservedSectors         dw 1
NumberofFats            db 2
RootEntries             dw 224
TotalSectors            dw 2880
Media                   db 0xF0
SectorsPerFat           dw 9
SectorsPerTrack         dw 18
HeadsPerCylinder        dw 2
HiddenSectors           dd 0
TotalBigSectors         dd 0
DriveNumber             db 0
Unused                  db 0
BootSignature           db 0x29
SerialNumber            dd 0x12345678
VolumeLabel             db "TEST OS    "
FileSystem              db "FAT12   "

boot:
        cli
        mov ax,0x07C0
        mov ds,ax
        mov es,ax
        mov fs,ax
        mov gs,ax

        mov ax,0x0000
        mov ss,ax
        mov sp,0xFFFF
        sti

        mov si,msgloading
        call print
        mov byte [DriveNumber], dl

loadRoot:

;find the size of root dir      
        xor cx,cx
        xor dx,dx
        mov ax,0x0020                   ;32 byte directory entry
        mul word [RootEntries]          ;Multiply by number of root entries
        div word [BytesPerSector]       
        xchg ax,cx
        
;lets try to find the start of the root dir now...

        mov al, byte [NumberofFats]
        mul word [SectorsPerFat]
        add ax, word [ReservedSectors]
        mov word [datasector],ax        
        add word [datasector], cx       

;Now let's finally read it into memory... at 7C00:0200

        mov bx, 0x0200
        call readSectors

;lets find our kernel file Very Happy
        mov cx, word [RootEntries]
        mov di,0x0200
.loopr:
        push cx
        mov cx, 0x000B          ;Eleven character name Razz
        mov si, KernName
        push di                 ;Save position of di...
        rep cmpsb
        pop di                  ;Restore starting position
        je loadFat              ;If it was the right name, load it!
        pop cx                  ;Restore cx
        add di, 0x0020          ;Up the memory location to the next entry
        loop .loopr
        jmp failure             ;we're a failure if it comes to this :'(

loadFat:
        
;save starting cluster of boot image

        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 [NumberofFats]
        mul word [SectorsPerFat]
        mov cx, ax
        
;compute location of FAT and store in ax

        mov ax, word [ReservedSectors]

;read FAT into memory (7C00:0200)

        mov bx, 0x0200
        call readSectors

; read image file into memory (0050:0000)

        mov ax, 0x0050
        mov es, ax
        mov bx, 0x0000
        push bx

loadImage:
        
        mov ax, word [cluster]
        pop bx
        call C2LBA
        xor cx,cx
        mov cl, byte [SectorsPerCluster]
        call readSectors
        push bx

;compute next cluster

        mov ax, word [cluster]
        mov cx, ax
        mov dx, ax
        shr dx, 0x0001
        add cx, dx
        mov bx, 0x0200
        add bx, cx
        mov dx, word [bx]
        test ax, 0x0001
        jnz .odd
.even:
        
        and dx, 0000111111111111b
        jmp .done
.odd:
        shr dx, 0x0004

.done:
        mov word [cluster], dx
        cmp dx, 0x0FF0
        jb loadImage
done:
        mov si, msgcrlf
        call print
        push word 0x0040
        push word 0x0100
        retf
failure:
        mov si, msgfailure
        call print
        mov ah, 0x00
        int 16h
        int 19h


;=======================================================
;FUNCTIONS GO HERE
;-------------------------------------------------------

print:
        lodsb
        or al,al
        jz .pdone
        mov ah,0eh
        int 10h
        jmp print
.pdone:
        ret

readSectors:
        mov di, 0x0005          ;Five retires for error
.loopr:
        push ax
        push bx
        push cx
        call LBA2CHS
        mov ah, 0x02
        mov al, 0x01
        mov ch, byte [absoluteTrack]
        mov cl, byte [absoluteSector]
        mov dh, byte [absoluteHead]
        mov dl, byte [DriveNumber]
        int 13h
        jnc .success
        xor ax,ax
        int 13h
        dec di
        pop cx
        pop bx
        pop ax
        jnz .loopr
        int 18h
.success:
        mov si, msgprogress
        call print
        pop cx
        pop bx
        pop ax
        add bx, word [BytesPerSector]
        inc ax
        loop readSectors
        ret
;************************************
;CHS TO LBA conversion
; LBA = (cluster - 2) * sectors per cluster
;**************************************
C2LBA:
        sub ax,0x0002
        xor cx,cx
        mov cl, byte [SectorsPerCluster]
        mul cx
        add ax, word [datasector]
        ret

;*********************************
;LBA to CHS
; 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)
;*********************************

LBA2CHS:
        xor dx,dx
        div word [SectorsPerTrack]
        inc dl
        mov byte [absoluteSector], dl
        xor dx,dx
        div word [HeadsPerCylinder]
        mov byte [absoluteHead], dl
        mov byte [absoluteTrack], al
        ret

absoluteSector db 0x00
absoluteHead db 0x00
absoluteTrack db 0x00

datasector dw 0x0000
cluster dw 0x0000
KernName db "KERN    COM"
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 0AA55h
    

as I bonus, here is a simple kernel I also wrote for you that sets up two MS-DOS interrupts and stack, prints a message, and then hangs. MAKE SURE THE FILE IS CALLED KERN.COM AND IS IN THE ROOT DIRECTORY OF THE 1.44 MEG, FAT12 FLOPPY!
Code:
org 100h
start:
        int     12h   ;get free memory
        shl     ax, 6 ;convert KB to paragraphs
        sub     ax, 2048/16  ; subtract 2048 bytes from it
        cli     ;disable interrupts
        mov     ss, ax      ;set up new stack
        mov     sp, 2048    ;set stack to 2048 bytes
        sti     ;re-enable interrupts
        push    0
        pop     ds  ;zero DS
        cli
        mov     word[ds:0084h], int21  ;set int 21h vector to us
        mov     word[ds:0086h], cs
        mov     word[ds:0080h], int20  ;set int 20h vector to us
        mov     word[ds:0082h], cs
        sti
        push    cs cs
        pop     ds es
;example simple DOS program
        mov     ah, 09
        mov     dx, msg
        int     21h
        int     20h
msg     db      "Hello World!$"
main:
        hlt
        cli
        jmp     $
int21: ;our ivt
        pushf
        cmp     ah, 09  ;ah = 09 is our only function so ya
        jz      int21_09
        mov     ax, 0xffff ;interrupt error, return error value
        popf
        iret  ;interrupt return
int21_09:
        mov     si, dx
@@:
        lodsb
        cmp     al, 24h ;look for $
        jz      @f
        mov     ah, 0eh
        int     10h
        jmp     @b
@@:
        popf
        iret
int20:
        jmp     main   ;for now main is just a jmp $, but this is where a program would return control to the kernel
    
Post 13 Sep 2011, 04:57
View user's profile Send private message Reply with quote
xleelz



Joined: 12 Mar 2011
Posts: 86
Location: In Google Code Server... waiting for someone to download me
xleelz 13 Sep 2011, 23:50
Quote:

"FATAL: INT18: BOOT FAILURE"
this interrupt is called when there is no bootable disk available to the system...
so, i think that you are trying to boot a disk that the bios don't have detected as bootable...
take a look in your bios

VirtualBox BIOS? Idk... I had used the same code and had a second stage bootloader and a 32bit kernel but I changed it to a different folder, took out the second stage bootloader and changed the file name of the file to load to a new kernel... and it shows an error now...


Quote:

are you sure the file is on the floppy and named correctly?

pretty sure, least Winimage says it is

Thanks for the modified code it works fine... but I still don't understand what went wrong...


[edit] Nvm... I realize what I did... the boot loader was fine, in my kernel code the first line was "use32" instead of "use16"... my bad Embarassed
Post 13 Sep 2011, 23:50
View user's profile Send private message Reply with quote
Display posts from previous:
Post new topic Reply to topic

Jump to:  


< Last Thread | Next Thread >
Forum Rules:
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum
You cannot attach files in this forum
You can download files in this forum


Copyright © 1999-2025, Tomasz Grysztar. Also on GitHub, YouTube.

Website powered by rwasa.