且构网

分享程序员开发的那些事...
且构网 - 分享程序员编程开发的那些事

引导加载程序未加载内核

更新时间:2023-12-05 20:27:04

如果您打算使用 MIKEOS 引导加载程序,那么您需要创建一个 FAT12 格式的 1.44MiB 软盘映像以与卷引导记录 (VBR) 兼容boot.asm.然后您需要将您的 KERNEL.BIN 复制到该图像中.

使用 mtools 包,这个过程非常简单.mtools


内核问题

kernel.asm 中的主要问题是:

  • DS 段寄存器设置不正确.MIKEOS 在内存中的 0x2000:0x0000 (segment:offset) 加载您的内核.您需要一个与偏移部分匹配的 ORG.您需要加载带有段部分 (0x2000) 的 DS(如果需要,还可以加载 ES).

  • 在使用像 LODS/STOS/SCAS 这样的字符串指令之前,您要确保方向标志 (DF) 设置为您期望的方式.使用 CLD 会将 DF=0 设置为向前移动,这是您的代码所期望的.

  • 您似乎还调用了 int 21h 进行打印.代码似乎是从 DOS 程序中遗留下来的,您打算将其删除.

  • 您在 cmd_shut 字符串中拼错了 shutdown.您错误地将其拼写为 shutdwon.

  • 不清楚你想用这段代码做什么:

     mov ah, 9 ;不清楚你在这里想做什么?mov bl, 9mov cx, 11整数 10 小时;???

您不妨考虑删除它.

可以将代码的开头修改为:

[位 16]组织 0x0000移动斧头,0x2000;设置段以匹配 CS=0x2000mov ds, ax移动,斧头异或斧头,斧头mov ss, ax ;将堆栈段设置为 0x0000mov sp, 0x7C00 ;堆栈从 0x0000:0x7C00 向下增长CL ;清除方向标志(DF=0 是向前的弦移动)动啊, 9 ;不清楚你在这里想做什么?mov bl, 9mov cx, 11整数 10 小时;???mov si, boota ;打印启动信息调用 print_string[剪辑]

您拼写错误 shutdown,因此它不会被正确识别为命令.应该是:

cmd_shut db 'shutdown', 0

通过这些更改,代码在运行时如下所示:

I am developing my Operating System.

I got error on booting my OS.

The error was:

KERNEL.BIN not found!

Here are the Codes:

Boot.asm

; The Aqua_Seven_OS Operating System bootloader
; ==================================================================


    BITS 16

    jmp short bootloader_start  ; Jump past disk description section
    nop             ; Pad out before disk description


; ------------------------------------------------------------------
; Disk description table, to make it a valid floppy
; Note: some of these values are hard-coded in the source!
; Values are those used by IBM for 1.44 MB, 3.5" diskette

OEMLabel        db "MIKEBOOT"   ; Disk label
BytesPerSector      dw 512      ; Bytes per sector
SectorsPerCluster   db 1        ; Sectors per cluster
ReservedForBoot     dw 1        ; Reserved sectors for boot record
NumberOfFats        db 2        ; Number of copies of the FAT
RootDirEntries      dw 224      ; Number of entries in root dir
                    ; (224 * 32 = 7168 = 14 sectors to read)
LogicalSectors      dw 2880     ; Number of logical sectors
MediumByte      db 0F0h     ; Medium descriptor byte
SectorsPerFat       dw 9        ; Sectors per FAT
SectorsPerTrack     dw 18       ; Sectors per track (36/cylinder)
Sides           dw 2        ; Number of sides/heads
HiddenSectors       dd 0        ; Number of hidden sectors
LargeSectors        dd 0        ; Number of LBA sectors
DriveNo         dw 0        ; Drive No: 0
Signature       db 41       ; Drive signature: 41 for floppy
VolumeID        dd 00000000h    ; Volume ID: any number
VolumeLabel     db "MIKEOS     "; Volume Label: any 11 chars
FileSystem      db "FAT12   "   ; File system type: don't change!


; ------------------------------------------------------------------
; Main bootloader code

bootloader_start:
    mov ax, 07C0h           ; Set up 4K of stack space above buffer
    add ax, 544         ; 8k buffer = 512 paragraphs + 32 paragraphs (loader)
    cli             ; Disable interrupts while changing stack
    mov ss, ax
    mov sp, 4096
    sti             ; Restore interrupts

    mov ax, 07C0h           ; Set data segment to where we're loaded
    mov ds, ax

    ; NOTE: A few early BIOSes are reported to improperly set DL

    cmp dl, 0
    je no_change
    mov [bootdev], dl       ; Save boot device number
    mov ah, 8           ; Get drive parameters
    int 13h
    jc fatal_disk_error
    and cx, 3Fh         ; Maximum sector number
    mov [SectorsPerTrack], cx   ; Sector numbers start at 1
    movzx dx, dh            ; Maximum head number
    add dx, 1           ; Head numbers start at 0 - add 1 for total
    mov [Sides], dx

no_change:
    mov eax, 0          ; Needed for some older BIOSes


; First, we need to load the root directory from the disk. Technical details:
; Start of root = ReservedForBoot + NumberOfFats * SectorsPerFat = logical 19
; Number of root = RootDirEntries * 32 bytes/entry / 512 bytes/sector = 14
; Start of user data = (start of root) + (number of root) = logical 33

floppy_ok:              ; Ready to read first block of data
    mov ax, 19          ; Root dir starts at logical sector 19
    call l2hts

    mov si, buffer          ; Set ES:BX to point to our buffer (see end of code)
    mov bx, ds
    mov es, bx
    mov bx, si

    mov ah, 2           ; Params for int 13h: read floppy sectors
    mov al, 14          ; And read 14 of them

    pusha               ; Prepare to enter loop


read_root_dir:
    popa                ; In case registers are altered by int 13h
    pusha

    stc             ; A few BIOSes do not set properly on error
    int 13h             ; Read sectors using BIOS

    jnc search_dir          ; If read went OK, skip ahead
    call reset_floppy       ; Otherwise, reset floppy controller and try again
    jnc read_root_dir       ; Floppy reset OK?

    jmp reboot          ; If not, fatal double error


search_dir:
    popa

    mov ax, ds          ; Root dir is now in [buffer]
    mov es, ax          ; Set DI to this info
    mov di, buffer

    mov cx, word [RootDirEntries]   ; Search all (224) entries
    mov ax, 0           ; Searching at offset 0


next_root_entry:
    xchg cx, dx         ; We use CX in the inner loop...

    mov si, kern_filename       ; Start searching for kernel filename
    mov cx, 11
    rep cmpsb
    je found_file_to_load       ; Pointer DI will be at offset 11

    add ax, 32          ; Bump searched entries by 1 (32 bytes per entry)

    mov di, buffer          ; Point to next entry
    add di, ax

    xchg dx, cx         ; Get the original CX back
    loop next_root_entry

    mov si, file_not_found      ; If kernel is not found, bail out
    call print_string
    jmp reboot


found_file_to_load:         ; Fetch cluster and load FAT into RAM
    mov ax, word [es:di+0Fh]    ; Offset 11 + 15 = 26, contains 1st cluster
    mov word [cluster], ax

    mov ax, 1           ; Sector 1 = first sector of first FAT
    call l2hts

    mov di, buffer          ; ES:BX points to our buffer
    mov bx, di

    mov ah, 2           ; int 13h params: read (FAT) sectors
    mov al, 9           ; All 9 sectors of 1st FAT

    pusha               ; Prepare to enter loop


read_fat:
    popa                ; In case registers are altered by int 13h
    pusha

    stc
    int 13h             ; Read sectors using the BIOS

    jnc read_fat_ok         ; If read went OK, skip ahead
    call reset_floppy       ; Otherwise, reset floppy controller and try again
    jnc read_fat            ; Floppy reset OK?

; ******************************************************************
fatal_disk_error:
; ******************************************************************
    mov si, disk_error      ; If not, print error message and reboot
    call print_string
    jmp reboot          ; Fatal double error


read_fat_ok:
    popa

    mov ax, 2000h           ; Segment where we'll load the kernel
    mov es, ax
    mov bx, 0

    mov ah, 2           ; int 13h floppy read params
    mov al, 1

    push ax             ; Save in case we (or int calls) lose it


; Now we must load the FAT from the disk. Here's how we find out where it starts:
; FAT cluster 0 = media descriptor = 0F0h
; FAT cluster 1 = filler cluster = 0FFh
; Cluster start = ((cluster number) - 2) * SectorsPerCluster + (start of user)
;               = (cluster number) + 31

load_file_sector:
    mov ax, word [cluster]      ; Convert sector to logical
    add ax, 31

    call l2hts          ; Make appropriate params for int 13h

    mov ax, 2000h           ; Set buffer past what we've already read
    mov es, ax
    mov bx, word [pointer]

    pop ax              ; Save in case we (or int calls) lose it
    push ax

    stc
    int 13h

    jnc calculate_next_cluster  ; If there's no error...

    call reset_floppy       ; Otherwise, reset floppy and retry
    jmp load_file_sector


    ; In the FAT, cluster values are stored in 12 bits, so we have to
    ; do a bit of maths to work out whether we're dealing with a byte
    ; and 4 bits of the next byte -- or the last 4 bits of one byte
    ; and then the subsequent byte!

calculate_next_cluster:
    mov ax, [cluster]
    mov dx, 0
    mov bx, 3
    mul bx
    mov bx, 2
    div bx              ; DX = [cluster] mod 2
    mov si, buffer
    add si, ax          ; AX = word in FAT for the 12 bit entry
    mov ax, word [ds:si]

    or dx, dx           ; If DX = 0 [cluster] is even; if DX = 1 then it's odd

    jz even             ; If [cluster] is even, drop last 4 bits of word
                    ; with next cluster; if odd, drop first 4 bits

odd:
    shr ax, 4           ; Shift out first 4 bits (they belong to another entry)
    jmp short next_cluster_cont


even:
    and ax, 0FFFh           ; Mask out final 4 bits


next_cluster_cont:
    mov word [cluster], ax      ; Store cluster

    cmp ax, 0FF8h           ; FF8h = end of file marker in FAT12
    jae end

    add word [pointer], 512     ; Increase buffer pointer 1 sector length
    jmp load_file_sector


end:                    ; We've got the file to load!
    pop ax              ; Clean up the stack (AX was pushed earlier)
    mov dl, byte [bootdev]      ; Provide kernel with boot device info

    jmp 2000h:0000h         ; Jump to entry point of loaded kernel!


; ------------------------------------------------------------------
; BOOTLOADER SUBROUTINES

reboot:
    mov ax, 0
    int 16h             ; Wait for keystroke
    mov ax, 0
    int 19h             ; Reboot the system


print_string:               ; Output string in SI to screen
    pusha

    mov ah, 0Eh         ; int 10h teletype function

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

.done:
    popa
    ret


reset_floppy:       ; IN: [bootdev] = boot device; OUT: carry set on error
    push ax
    push dx
    mov ax, 0
    mov dl, byte [bootdev]
    stc
    int 13h
    pop dx
    pop ax
    ret


l2hts:          ; Calculate head, track and sector settings for int 13h
            ; IN: logical sector in AX, OUT: correct registers for int 13h
    push bx
    push ax

    mov bx, ax          ; Save logical sector

    mov dx, 0           ; First the sector
    div word [SectorsPerTrack]
    add dl, 01h         ; Physical sectors start at 1
    mov cl, dl          ; Sectors belong in CL for int 13h
    mov ax, bx

    mov dx, 0           ; Now calculate the head
    div word [SectorsPerTrack]
    mov dx, 0
    div word [Sides]
    mov dh, dl          ; Head/side
    mov ch, al          ; Track

    pop ax
    pop bx

    mov dl, byte [bootdev]      ; Set correct device

    ret


; ------------------------------------------------------------------
; STRINGS AND VARIABLES

    kern_filename   db "KERNEL  BIN"    ; kernel filename

    disk_error  db "Floppy error! Press any key...", 0
    file_not_found  db "KERNEL.BIN not found!", 0

    bootdev     db 0    ; Boot device number
    cluster     dw 0    ; Cluster of the file we want to load
    pointer     dw 0    ; Pointer into Buffer, for loading kernel


; ------------------------------------------------------------------
; END OF BOOT SECTOR AND BUFFER START

    times 510-($-$$) db 0   ; Pad remainder of boot sector with zeros
    dw 0AA55h       ; Boot signature (DO NOT CHANGE!)


buffer:             ; Disk buffer begins (8k after this, stack starts)


; ==================================================================

I found the boot code on internet.

Kernel.asm


[bits 16]



   mov ax, 0  ; set up segments
   mov ds, ax
   mov es, ax
   mov ss, ax     ; setup stack
   mov sp, 0x7C00 ; stack grows downwards from 0x7C00

   mov ah, 9
   mov bl, 9
   mov cx, 11 
   int 10h
   mov DX, boota
   int 21H

   mov si, boota         ;Print boot message
   call print_string

 mainloop:
   mov si, prompt
   call print_string          ; prompt db ">"

   mov di, buffer
   call get_string

   mov si, buffer
   cmp byte [si], 0  ; blank line?
   je mainloop       ; yes, ignore it

   mov si, buffer
   mov di, cmd_reb  ; "reboot" command
   call strcmp
   jc .reboot

   mov si, buffer
   mov di, cmd_shut  ; "shutdown" command
   call strcmp
   jc .shut

   mov si,badcommand
   call print_string     ; What if there is no such command?
   jmp mainloop        ; jmp mainloop :-)

 .reboot:                           ; reboot function
   db 0x0ea 
   dw 0x0000 
   dw 0xffff

 .shut:                                   ;shutdown function

   mov al, 02h      
   mov ah, 00h      
   int 10h

   mov si, shutm
   call print_string

   mov ax, 0x1000
   mov ax, ss
   mov sp, 0xf000
   mov ax, 0x5307
   mov bx, 0x0001
   mov cx, 0x0003
   int 0x15

   ; ------Variables-------------
 shutm  db 'The MCOS shutdowned sucessfully. Now you may power off the computer.', 0x0d, 0x0a, 0
 boota db 'Booting MotoSoft COS 1...', 0x0d, 0x0a, 0
 buffer times 64 db 0
 prompt db '>', 0
 badcommand db 'Bad command entered.', 0x0D, 0x0A, 0 
 cmd_reb db 'reboot', 0


 ; ================
 ; calls start here
 ; ================

 print_string:
   lodsb        ; grab a byte from SI

   or al, al  ; logical or AL by itself
   jz .done   ; if the result is zero, get out

   mov ah, 0x0E
   int 0x10      ; otherwise, print out the character!

   jmp print_string

 .done:
   ret

 get_string:
   xor cl, cl

 .loop:
   mov ah, 0
   int 0x16   ; wait for keypress

   cmp al, 0x08    ; backspace pressed?
   je .backspace   ; yes, handle it

   cmp al, 0x0D  ; enter pressed?
   je .done      ; yes, we're done

   cmp cl, 0x3F  ; 63 chars inputted?
   je .loop      ; yes, only let in backspace and enter
   mov ah, 0x0E
   int 0x10      ; print out character

   stosb  ; put character in buffer
   inc cl
   jmp .loop

 .backspace:
   cmp cl, 0    ; beginning of string?
   je .loop ; yes, ignore the key

   dec di
   mov byte [di], 0 ; delete character
   dec cl       ; decrement counter as well

   mov ah, 0x0E
   mov al, 0x08
   int 10h      ; backspace on the screen

   mov al, ' '
   int 10h      ; blank character out

   mov al, 0x08
   int 10h      ; backspace again

   jmp .loop    ; go to the main loop

 .done:
   mov al, 0    ; null terminator
   stosb

   mov ah, 0x0E
   mov al, 0x0D
   int 0x10
   mov al, 0x0A
   int 0x10     ; newline

   ret

 strcmp:
 .loop:
   mov al, [si]   ; grab a byte from SI
   mov bl, [di]   ; grab a byte from DI
   cmp al, bl     ; are they equal?
   jne .notequal  ; nope, we're done.

   cmp al, 0  ; are both bytes (they were equal before) null?
   je .done   ; yes, we're done.

   inc di     ; increment DI
   inc si     ; increment SI
   jmp .loop  ; loop!

 .notequal:
   clc  ; not equal, clear the carry flag
   ret

 .done:     
   stc  ; equal, set the carry flag
   ret


cmd_shut db 'shutdwon', 0```

I got all these codes from internet and i am making my HOBBY OS.

And the compiling Codes:-

nasm -f bin -o boot.bin boot.asm
nasm -f bin -o kernel.bin kernel.asm
dd if=/dev/zero of=disk.img bs=512 count=2880
dd if=boot.bin of=disk.img bs=512 conv=notrunc
dd if=kernel.bin of=disk.img bs=512 seek=1 conv=notrunc

When I boot my OS, it shows

KERNEL.BIN not found!

Image of error:

If you intend on using the MIKEOS bootloader then you need to create a FAT12 formatted 1.44MiB floppy disk image to be compatible with the volume boot record (VBR) in boot.asm. You then need to copy your KERNEL.BIN into that image.

This process is quite simple with the mtools package. mtools has online documentation. This answer isn't a complete guide to using mtools but enough to do what you need to boot. If you are using Debian or a Debian based distro like Ubuntu you can install the mtools package as root user with:

apt-get install mtools

The mtools package comes with a mformat program that can create 1.44MiB disk image; format it as FAT12; and have it automatically place your boot.bin program in the first sector. The command would be:

mformat -f1440 -B boot.bin -C -i disk.img

This should create a 1.44MiB disk image file called disk.img. To copy a file like KERNEL.BIN into disk.img you'd use the command:

mcopy -D o -i disk.img KERNEL.BIN ::/

The -D o option forces mcopy to overwrite a file if it exists. -i disk.img specifies the name of the disk image file KERNEL.BIN is the file we want to copy into the image (source file(s)). :: is a special device name to refer to the disk image itself. The / is the root directory. Together ::/ at the end of the command is the target location to put the file - in the root directory of the disk image.

You can use the mdir command to get a file listing of the root directory.

mdir -i disk.img ::/

This works similar to dir / in DOS. The output would look something like:

 Volume in drive : has no label
 Volume Serial Number is 6F67-C526
Directory for ::/

KERNEL   BIN        74 2019-12-20  13:25
        1 file                   74 bytes
                          1 457 152 bytes free

I have created a kernel.asm that replaces yours as yours has problems that are beyond the scope of your question. I provide this one as a sample that should work:

ORG 0x0000

start:
    mov ax, 0x2000             ; Mike OS'es bootloader loads us at 0x2000:0x0000
    mov ds, ax                 ; Set DS = ES = 0x2000
    mov es, ax

    ; Stack just below 0x2000:0x0000 starting at 0x1000:0x0000.
    ; First push will set SS:SP to 0x1000:0xfffe because SP will wrap.
    mov ax, 0x1000
    mov ss, ax
    xor sp, sp

    cld                        ; Clear Direction Flag (DF=0 is forward string movement)

    mov si, testCodeStr
    call print_string

    cli
.end_loop:
    hlt
    jmp .end_loop

testCodeStr: db 0x0d, 0x0a, "KERNEL.BIN loaded and running...", 0

; Function: print_string
;           Display a string to the console on display page 0
;
; Inputs:   SI = Offset of address to print
; Clobbers: AX, BX, SI

print_string:
    mov ah, 0x0e                ; BIOS tty Print
    xor bx, bx                  ; Set display page to 0 (BL)
    jmp .getch
.repeat:
    int 0x10                    ; print character
.getch:
    lodsb                       ; Get character from string
    test al,al                  ; Have we reached end of string?
    jnz .repeat                 ;     if not process next character
.end:
    ret

This code is intended to work with MIKEOS's bootloader that loads and runs the kernel from 0x2000:0x0000 in memory. I use an ORG 0x0000 at the top and set DS and ES to 0x2000 to correspond to where we are loaded in memory. I also set SS:SP to an initial value of 0x1000:00000. The first time you push a 16-bit value on the stack SS:SP will be 0x1000:0xFFFE (physical address 0x1FFFE) just below the load address of the kernel at 0x2000:0x0000 (physical address 0x20000).

When assembled and the disk image built and run in QEMU with the commands:

nasm -f bin boot.asm -o boot.bin
nasm -f bin kernel.asm -o KERNEL.BIN
mformat -f1440 -B boot.bin -C -i disk.img
mcopy -D o -i disk.img KERNEL.BIN ::/

qemu-system-i386 -fda disk.img

The output should look similar to:


Kernel problems

The main problems in your kernel.asm are:

  • Incorrectly setting the DS segment register. MIKEOS loaded your kernel at 0x2000:0x0000 (segment:offset) in memory. You need an ORG that matches the offset portion. You will want to load the DS (and if need be the ES) with the segment portion (0x2000).

  • Before using string instructions like LODS/STOS/SCAS you want to ensure the Direction Flag (DF) is set the way you expect. Using CLD will set DF=0 for forward movement which is what your code expects.

  • It also appears that you call int 21h to print. It seems that code was left over from a DOS program and you meant to remove it.

  • You misspelled shutdown in the cmd_shut string. You incorrectly spelled it as shutdwon.

  • It is unclear what you wanted to do with this code:

      mov ah, 9      ; Unclear what you were trying to do here?
      mov bl, 9
      mov cx, 11
      int 10h        ; ????
    

You may wish to consider deleting it.

The beginning of your code could be modified to look like:

[bits 16]
ORG 0x0000

   mov ax, 0x2000 ; set up segments to match CS=0x2000
   mov ds, ax
   mov es, ax
   xor ax, ax
   mov ss, ax     ; set stack segment to 0x0000
   mov sp, 0x7C00 ; stack grows downwards from 0x0000:0x7C00
   cld            ; Clear Direction Flag (DF=0 is forward string movement)    

   mov ah, 9      ; Unclear what you were trying to do here?
   mov bl, 9
   mov cx, 11
   int 10h        ; ????

   mov si, boota  ; Print boot message
   call print_string
   [snip]

You spelled shutdown incorrectly so it won't be properly recognized as a command. It should be:

cmd_shut db 'shutdown', 0

With these changes the code looks like this when run: