It’s finally time to put together the first and second stage bootloaders we’ve seen so far and make them work – although if you’ve been programming along with the past few installments of this series, you may already have done so. In the last few sections, we looked at the Intel 80386 processor’s protected mode and what’s required to get to it.

In this part, we’ll take a short break and put everything we’ve done so far together to see it run. Might as well have a little payoff for all the work, right?

This article is going to repeat all the code presented in the previous articles to see how it all goes together. You can read through it, or you can grab all the source code here.

This article is part of a series on toy operating system development.

View the series index

How it all works

Before we get to code, let’s have a summary of everything that happens during the boot process. Loading the boot sector

  • When it’s switched on, the computer performs a Power-On Self Test (POST). It then detects whether a bootable disk is inserted in the disk drive, and loads its boot sector (the first 512 bytes on the floppy disk). A boot sector is executable if its last two bytes are the magic value 0xaa55.
  • The entire boot sector is loaded at address 0000:7c00, and the CPU starts executing the very first instruction found at that address.
  • Only the first 3 bytes of the boot sector can be code. The next 59 are boot data bytes that describe the floppy disk. The executable code continues after that. In that code, we have to do everything necessary to load the second-stage bootloader.

First-stage bootloader

In the first-stage bootloader, we must do the following:

  • Setup the memory segments and stack used by the bootloader code
  • Reset the disk system
  • Display a string saying “Loading OS…”
  • Find the second-stage boot loader in the FAT directory
  • Read the second-stage boot loader image into memory at 1000:0000
  • Transfer control to the second-stage bootloader

We must leave the rest of the steps to get to protected mode and load the kernel to the second-stage bootloader, as there simply isn’t enough space available in the first-stage bootloader to do all this.

Second-stage bootloader

In the second-stage bootloader, we must do the following:

  • Copy the boot sector data bytes to a local memory area, as they will be overwritten
  • Find the kernel image in the FAT directory
  • Read the kernel image into memory at 2000:0000
  • Reset the disk system
  • Enable the A20 line
  • Setup the interrupt descriptor table at 0000:0000
  • Setup the global descriptor table at 0000:0800
  • Load the descriptor tables into the CPU
  • Switch to protected mode
  • Clear the prefetch queue
  • Setup protected mode memory segments and stack for use by the kernel code
  • Transfer control to the kernel code using a long jump

Boot sector structure

Both of our bootloaders will need to know the structure of the boot sector data bytes: bootsector:

  iOEM:        .ascii "DevOS   "    # OEM String
  iSectSize:   .word  0x200         # Bytes per sector
  iClustSize:  .byte  1             # Sectors per cluster
  iResSect:    .word  1             # #of reserved sectors
  iFatCnt:     .byte  2             # #of fat copies
  iRootSize:   .word  224           # size of root directory
  iTotalSect:  .word  2880          # total # of sectors if below 32 MB
  iMedia:      .byte  0xF0          # Media Descriptor
  iFatSize:    .word  9             # Size of each FAT
  iTrackSect:  .word  9             # Sectors per track
  iHeadCnt:    .word  2             # number of read-write heads
  iHiddenSect: .int   0             # number of hidden sectors
  iSect32:     .int   0             # # sectors if over 32 MB
  iBootDrive:  .byte  0             # holds drive that the boot sector came from
  iReserved:   .byte  0             # reserved, empty
  iBootSign:   .byte  0x29          # extended boot sector signature
  iVolID:      .ascii "seri"        # disk serial
  acVolLabel:  .ascii "MYVOLUME   " # just placeholder. We don't yet use volume labels.
  acFSType:    .ascii "FAT16   "    # file system type

Required macros

Some of the assembler code that we write for the bootloaders takes the form of functions that we will call multiple times. Other code is called only once and implemented in the form of macros, which serve merely to give structure to the code (we could not use macros, but then our code would become a very long and unreadable list of assembly instructions). For reference, I will present the macros used here.

mInitSegments

The first-stage bootloader must setup real-mode memory segments to work with, as well as a stack. The boot sector is loaded by the BIOS at 0000:7c00. We will define a stack at 0000:7c00, which will grown downward from there (as stacks always do). We must disable interrupts while we define our memory segments.

.macro mInitSegments
  cli                    # Disable interrupts
  mov  iBootDrive, dl    # save what drive we booted from (should be 0x0)
  mov  ax, cs            # CS is set to 0x0
  mov  ds, ax            # DS = CS = 0x0
  mov  es, ax            # ES = CS = 0x0
  mov  ss, ax            # SS = CS = 0x0
  mov  sp, 0x7C00        # Stack grows down from offset 0x7C00 toward 0x0000.
  sti                    # Enable interrupts
.endm

mResetDiskSystem

Our first-stage bootloader will need to read the FAT table from disk and find the second-stage bootloader image in it. To do so, it must first reset the disk system through the floppy disk controller. If this should fail, we cannot continue and must reboot.

.macro mResetDiskSystem
  mov  dl, iBootDrive    # drive to reset
  xor  ax, ax            # subfunction 0
  int  0x13              # call interrupt 13h
  jc   bootFailure       # display error message if carry set (error)
.endm

mFindFile

This macro loads the root directory of the floppy disk’s FAT into memory at the provided segment loadsegment. It then looks for filename and finds the disk sector where this file begins as well as the number of sectors it occupies. These values are stored for later use. If the filename is not found in the FAT, then the system shows an error message and reboots.

This macro makes use of the ReadSector function which we will show below.

.macro mFindFile filename, loadsegment

  # The root directory will be loaded in a higher segment.
  # Set ES to this segment.
  mov     ax, loadsegment
  mov     es, ax

  # The number of sectors that the root directory occupies
  # is equal to its max number of entries, times 32 bytes per
  # entry, divided by sector size.
  # E.g. (32 * rootsize) / 512
  # This normally yields 14 sectors on a FAT12 disk.
  # We calculate this total, then store it in cx for later use in a loop.
  mov     ax, 32
  xor     dx, dx
  mul     word ptr iRootSize
  div     word ptr iSectSize          # Divide (dx:ax,sectsize) = (ax,dx)
  mov     cx, ax
  mov     root_scts, cx
  # root_scts is now the number of sectors in root directory.

  # Calculate start sector root directory:
  # root_strt = number of FAT tables * sectors per FAT
  #           + number of hidden sectors
  #           + number of reserved sectors
  xor   ax, ax                      # find the root directory
  mov   al, byte ptr iFatCnt        # ax = number of FAT tables
  mov   bx, word ptr iFatSize       # bx = sectors per FAT
  mul   bx                          # ax = #FATS * sectors per FAT
  add   ax, word ptr iHiddenSect    # Add hidden sectors to ax
  adc   ax, word ptr iHiddenSect+2
  add   ax, word ptr iResSect       # Add reserved sectors to ax
  mov   root_strt, ax
  # root_strt is now the number of the first root sector

  # Load a sector from the root directory.
  # If sector reading fails, a reboot will occur.
  read_next_sector:
  push   cx
  push   ax
  xor    bx, bx
  call   ReadSector

check_entry:
  mov    cx, 11                      # Directory entries filenames are 11 bytes.
  mov    di, bx                      # es:di = Directory entry address
  lea    si, filename               # ds:si = Address of filename we are looking for.
  repz   cmpsb                       # Compare filename to memory.
  je     found_file                  # If found, jump away.
  add    bx, word ptr 32             # Move to next entry. Complete entries are 32 bytes.
  cmp    bx, word ptr iSectSize      # Have we moved out of the sector yet?
  jne    check_entry                 # If not, try next directory entry.

  pop    ax
  inc    ax                          # check next sector when we loop again
  pop    cx
  loopnz read_next_sector            # loop until either found or not
  jmp    bootFailure                 # could not find file: abort

found_file:
  # The directory entry stores the first cluster number of the file
  # at byte 26 (0x1a). BX is still pointing to the address of the start
  # of the directory entry, so we will go from there.
  # Read cluster number from memory:
  mov    ax, es:[bx+0x1a]
  mov    file_strt, ax
.endm

mReadFAT

The mReadFAT macro loads the floppy disk’s FAT into memory at a specified segment. This macro also makes use of the ReadSector function. Once the FAT is loaded, it will be used by the mReadFile macro to actually read a file.

.macro mReadFAT fatsegment
  # The FAT will be loaded in a special segment.
  # Set ES to this segment.
  mov   ax, fatsegment
  mov   es, ax

  # Calculate offset of FAT:
  mov   ax, word ptr iResSect       # Add reserved sectors to ax
  add   ax, word ptr iHiddenSect    # Add hidden sectors to ax
  adc   ax, word ptr iHiddenSect+2

  # Read all FAT sectors into memory:
  mov   cx, word ptr iFatSize       # Number of sectors in FAT
  xor   bx, bx                      # Memory offset to read into (es:bx)
read_next_fat_sector:
  push  cx
  push  ax
  call  ReadSector
  pop   ax
  pop   cx
  inc   ax
  add   bx, word ptr iSectSize
  loopnz read_next_fat_sector       # continue with next sector
.endm

mReadFile

This macro reads a file image into memory at the specified memory segment. It uses the FAT table in memory read earlier by the mReadFAT macro. It also makes use of the start sector and number of sectors of the file to be read, which were earlier determined by the mFindFile macro.

.macro mReadFile loadsegment, fatsegment
  # Set memory segment that will receive the file:
  mov     ax, loadsegment
  mov     es, ax
  # Set memory offset for loading to 0.
  xor     bx, bx

  # Set memory segment for FAT:
  mov     cx, file_strt             # CX now points to file's first FAT entry

read_file_next_sector:
  # Locate sector:
  mov     ax, cx                    # Sector to read is equal to current FAT entry
  add     ax, root_strt             # Plus the start of the root directory
  add     ax, root_scts             # Plus the size of the root directory
  sub     ax, 2                     # ... but minus 2

  # Read sector:
  push    cx                        # Read a sector from disk, but save CX
  call    ReadSector                # as it contains our FAT entry
  pop     cx
  add     bx, iSectSize             # Move memory pointer to next section

  # Get next sector from FAT:
  push    ds                        # Make DS:SI point to FAT table
  mov     dx, fatsegment           # in memory.
  mov     ds, dx

  mov     si, cx                    # Make SI point to the current FAT entry
  mov     dx, cx                    # (offset is entry value * 1.5 bytes)
  shr     dx
  add     si, dx

  mov     dx, ds:[si]               # Read the FAT entry from memory
  test    dx, 1                     # See which way to shift
  jz      read_next_file_even
  and     dx, 0x0fff
  jmp     read_next_file_cluster_done
read_next_file_even:
  shr     dx, 4
read_next_file_cluster_done:
  pop     ds                        # Restore DS to the normal data segment
  mov     cx, dx                    # Store the new FAT entry in CX
  cmp     cx, 0xff8                 # If the FAT entry is greater or equal
  jl      read_file_next_sector     # to 0xff8, then we've reached end-of-file
.endm

mStartSecondStage

This macro sets up data segments for the second stage bootloader code which was loaded at 1000:0000. It then performs a long jump to the second-stage code, thus causing the code segment to point to the code’s location.

.macro mStartSecondStage
  # Make es and ds point to segment where 2nd stage was loaded.
  mov     ax, word ptr LOAD_SEGMENT
  mov     es, ax
  mov     ds, ax
  # Jump to second stage start of code:
  jmp     LOAD_SEGMENT:0
.endm

mCopyBootSector

The second-stage bootloader requires the data in the boot sector as well. When the second stage runs, the first thing it does is copy the boot sector data to a local memory area, before it gets overwritten.

.macro mCopyBootSector
  push     ds             # The original boot sector as loaded at 0000:7c00
  xor      ax, ax         # The actual bootsector data there starts at 0000:7c03
  mov      ds, ax         # Set ds:si to point to 0000:7c03
  mov      si, 0x7c03
  lea      di, bootsector # Set es:di to point to bootsector area in our code.
  mov      cx, 34         # Copy 34 bytes (the entire boot sector)
  rep      movsb
  pop      ds
.endm

mGoProtected

This macro switches the CPU to protected mode by setting the least significant bit in the CR0 register.

.macro mGoProtected
  mov    eax, cr0
  or     eax, 1
  mov    cr0, eax
.endm

mClearPrefetchQueue

This macro clears the CPU’s prefetch queue. This must be done just after switching to protected mode, since any instructions that the CPU has prefetched will have been decoded as 16 bit code. Since we are now in 32-bit mode, we must discard these decoded instructions and have the CPU fetch the instructions again. This is done by performing an absolute jump.

.macro mClearPrefetchQueue
  jmp    clear_prefetch_queue
clear_prefetch_queue:
  cld
clear_prefetch_queue__delay:
  mov    cx, 0xffff
  nop
  loopz  clear_prefetch_queue__delay
.endm

mSetup386Segments

Before we jump to the kernel code, we must setup the data segments and stack that the kernel will use. Since we are in protected mode at this point, we no longer specify segmented addresses but must use a selector instead. Also, we define a stack at 0x30000 (linear address) that will grow downwards.

.macro mSetup386Segments
  mov    ax, 0x10
  mov    ds, ax
  mov    es, ax
  mov    fs, ax
  mov    gs, ax
  mov    ss, ax
  mov    esp, 0x2ffff
.endm

mJumpToKernel

This final macro transfers control to the kernel code. It does this by executing a long jump, which will set the code segment cs to point to the kernel code. This has to be a 32-bit long jump, since we are not in protected mode. However, all of this code gets compiled as 16-bit code, so we need to encode the 32-bit instruction ourselves, just like a 32-bit assembler would:

.macro mJumpToKernel
  .byte 0x66
  .byte 0xEA
  .int  0x20000   # offset
  .word 0x0008    # selector word
.endm

Required functions

Apart from the above macros, we must write a number of functions that our bootloaders will use.

WriteString

The WriteString function writes a string to the terminal. It does this using BIOS interrupt 0x10, function 0xe. This can only be done while we’re still in real mode. After the switch to protected mode, we’ll need to write our own functions to write to the screen, since we can’t use the BIOS anymore.

This function expects a NULL-terminated string at ds:si.

.func WriteString
WriteString:
  lodsb                   # load byte at ds:si into al (advancing si)
  or     al, al           # test if character is 0 (end)
  jz     WriteString_done # jump to end if 0.

  mov    ah, 0xe          # Subfunction 0xe of int 10h (video teletype output).
  mov    bx, 9            # Set bh (page number) to 0, and bl (attribute) to white (9).
  int    0x10             # call BIOS interrupt.

  jmp    WriteString      # Repeat for next character.

WriteString_done:
  retw
.endfunc

Reboot

This function displays a message “Press any key…”, waits for a keypress, then reboots. The keypress is read using BIOS interrupt 0x16, function 0x0. Again, this can only be done while we’re still in real mode. After the switch to protected mode, we’ll need to write our own functions to write to the screen, since we can’t use the BIOS anymore.

.func Reboot
Reboot:
  lea    si, rebootmsg    # Load address of reboot message into si
  call   WriteString      # print the string
  xor    ax, ax           # subfuction 0
  int    0x16             # call bios to wait for key

  .byte  0xEA             # machine language to jump to FFFF:0000 (reboot)
  .word  0x0000
  .word  0xFFFF
.endfunc

ReadSector

This last function reads a sector from the floppy disk and stores it in es:bx. The sector logical address is provided in register ax. This function uses BIOS interrupt 0x13, function 0x2 to do the reading. Note that floppy disks are not very reliable, so the code attempts to read the sector data four times before giving up. If it gives up, the boot process fails and the system reboots.

.func ReadSector
ReadSector:
  xor     cx, cx                      # Set try count = 0

readsect:
  push    ax                          # Store logical block
  push    cx                          # Store try number
  push    bx                          # Store data buffer offset

  # Calculate cylinder, head and sector:
  # Cylinder = (LBA / SectorsPerTrack) / NumHeads
  # Sector   = (LBA mod SectorsPerTrack) + 1
  # Head     = (LBA / SectorsPerTrack) mod NumHeads

  mov     bx, iTrackSect              # Get sectors per track
  xor     dx, dx
  div     bx                          # Divide (dx:ax/bx to ax,dx)
  # Quotient (ax) =  LBA / SectorsPerTrack
  # Remainder (dx) = LBA mod SectorsPerTrack
  inc     dx                          # Add 1 to remainder, since sector
  mov     cl, dl                      # Store result in cl for int 13h call.

  mov     bx, iHeadCnt                # Get number of heads
  xor     dx, dx
  div     bx                          # Divide (dx:ax/bx to ax,dx)
  # Quotient (ax) = Cylinder
  # Remainder (dx) = head
  mov     ch, al                      # ch = cylinder
  xchg    dl, dh                      # dh = head number

  # Call interrupt 0x13, subfunction 2 to actually
  # read the sector.
  # al = number of sectors
  # ah = subfunction 2
  # cx = sector number
  # dh = head number
  # dl = drive number
  # es:bx = data buffer
  # If it fails, the carry flag will be set.
  mov     ax, 0x0201                  # Subfunction 2, read 1 sector
  mov     dl, iBootDrive              # from this drive
  pop     bx                          # Restore data buffer offset.
  int     0x13
  jc      readfail

  # On success, return to caller.
  pop     cx                          # Discard try number
  pop     ax                          # Get logical block from stack
  ret

  # The read has failed.
  # We will retry four times total, then jump to boot failure.
readfail:
  pop     cx                          # Get try number
  inc     cx                          # Next try
  cmp     cx, word ptr 4              # Stop at 4 tries
  je      bootFailure

  # Reset the disk system:
  xor     ax, ax
  int     0x13

  # Get logical block from stack and retry.
  pop     ax
  jmp     readsect
.endfunc

Enabling the A20 line

The second-stage bootloader will need to enable the processors 21st address line (see this article for an in-depth explanation). The following functions and macros do just this.

CheckA20

This function checks whether the A20 line is currently enable. It does this by testing whether the memory “wraps” at the one megabyte mark.

.func CheckA20
CheckA20:
  pushf
  push ds
  push es
  push di
  push si
  cli

  xor ax, ax                         # Set es:di = 0000:0500
  mov es, ax
  mov di, 0x0500

  not ax                             # Set ds:si = ffff:0510
  mov ds, ax
  mov si, 0x0510

  mov al, byte ptr es:[di]           # Save byte at es:di on stack.
  push ax

  mov al, byte ptr ds:[si]           # Save byte at ds:si on stack.
  push ax

  mov byte ptr es:[di], 0x00         # [es:di] = 0x00
  mov byte ptr ds:[si], 0xFF         # [ds:si] = 0xff

  cmp byte ptr es:[di], 0xFF         # Did memory wrap around?

  pop ax
  mov byte ptr ds:[si], al           # Restore byte at ds:si

  pop ax
  mov byte ptr es:[di], al           # Restore byte at es:di

  mov ax, 0
  je check_a20__exit                 # If memory wrapped around, return 0.

  mov ax, 1                          # else return 1.

check_a20__exit:
  pop si
  pop di
  pop es
  pop ds
  popf
  ret
.endfunc

mSetA20BIOS

This macro uses BIOS interrupt 0x15, function 0x2401 to attempt to enable the A20 line.

.macro mSetA20BIOS
  mov ax, 0x2401
  int 0x15
.endm

Wait_8042_command

This function has the CPU wait until the 8042 keyboard controller is ready to accept a command byte.

.func Wait_8042_command
Wait_8042_command:
  in      al,0x64
  test    al,2
  jnz     Wait_8042_command
  ret
.endfunc

Wait_8042_data

This function has the CPU wait until the 8042 keyboard controller is ready to accept a data byte.

.func Wait_8042_data
Wait_8042_data:
  in      al,0x64
  test    al,1
  jz      Wait_8042_data
  ret
.endfunc

mSetA20Keyboard

This macro uses the 8042 keyboard controller chip to attempt to enable the A20 line.

.macro mSetA20Keyboard
  cli                        # Disable interrupts

  call    Wait_8042_command  # When controller ready for command
  mov     al,0xAD            # Send command 0xad (disable keyboard).
  out     0x64,al

  call    Wait_8042_command  # When controller ready for command
  mov     al,0xD0            # Send command 0xd0 (read from input)
  out     0x64,al

  call    Wait_8042_data     # When controller has data ready
  in      al,0x60            # Read input from keyboard
  push    eax                # ... and save it

  call    Wait_8042_command  # When controller is ready for command
  mov     al,0xD1            # Set command 0xd1 (write to output)
  out     0x64,al

  call    Wait_8042_command  # When controller is ready for command
  pop     eax                # Write input back, with bit #2 set
  or      al,2
  out     0x60,al

  call    Wait_8042_command  # When controller is ready for command
  mov     al,0xAE            # Write command 0xae (enable keyboard)
  out     0x64,al

  call    Wait_8042_command  # Wait until controller is ready for command

  sti                        # Enable interrupts
.endm

mSetA20FastGate

This macro attempts to enable the A20 line by using the “Fast A20” method, which is a special port that some chipsets have.

.macro mSetA20FastGate
  in al, 0x92
  or al, 2
  out 0x92, al
.endm

mEnableA20

This final macro combines all previous A20 macros to enable the A20 line. If none of the methods work, the macro gives up and reboots the system.

.macro mEnableA20
  call CheckA20
  cmp  ax, 0
  jne  enable_A20__done
  mSetA20BIOS
  call CheckA20
  cmp  ax, 0
  jne  enable_A20__done
  mSetA20Keyboard
  call CheckA20
  cmp  ax, 0
  jne  enable_A20__done
  mSetA20FastGate
  call CheckA20
  xchg bx, bx
  cmp  ax, 0
  jne  enable_A20__done
enable_A20__fail:
  mWriteString a20error
  mReboot
enable_A20__done:
.endm

Macros for descriptor tables

The second-stage bootloader will need to setup a global descriptor table (GDT) and an empty interrupt descriptor table (IDT). The following macros take care of that:

mSetupGDT

This macro creates a GDT with three entries:

  • A NULL-descriptor (required)
  • A code segment of 4GB, starting at 0x0
  • A data segment of 4GB, starting at 0x0
.macro mSetupGDT
  mSetupGDT:

  # NULL Descriptor:
  mov   cx, 4                         # Write the NULL descriptor,
  rep   stosw                         # which is 4 zero-words.

  # Code segment descriptor:
  mov   es:[di],   word ptr 0xffff    # limit = 0xffff (since granularity
                                      # bit is set, this is 4 GB)
  mov   es:[di+2], word ptr 0x0000    # base = 0x0000
  mov   es:[di+4], byte ptr 0x0       # base
  mov   es:[di+5], byte ptr 0x9a      # access = 0x9a (see above)
  mov   es:[di+6], byte ptr 0xcf      # flags + limit = 0xcf (see above)
  mov   es:[di+7], byte ptr 0x00      # base
  add   di, 8

  # Data segment descriptor:
  mov   es:[di],   word ptr 0xffff    # limit = 0xffff (since granularity
                                      # bit is set, this is 4 GB)
  mov   es:[di+2], word ptr 0x0000    # base = 0x0000
  mov   es:[di+4], byte ptr 0x0       # base
  mov   es:[di+5], byte ptr 0x92      # access = 0x92 (see above)
  mov   es:[di+6], byte ptr 0xcf      # flags + limit = 0xcf (see above)
  mov   es:[di+7], byte ptr 0x00      # base
.endm

mSetupIDT

This macro creates an interrupt descriptor table at 0000:0000. It has 256 entries of 8 bytes each, all filled with zeroes. The presence of an IDT is required to switch to protected mode, but we don’t need to define any interrupt handlers yet.

.macro mSetupIDT
mSetupIDT:
  mov   ax, 0x0000      # Have es:di point to 0000:0000
  mov   es, ax
  mov   di, 0
  mov   cx, 2048        # Write 2048 zeroes
  rep   stosb           # since the 2048 has 256 entries of 8 bytes.
.endm

mLoadDescriptorTables

This final macro tells the CPUs where the GDT and the IDT are:

.macro mLoadDescriptorTables
  lgdt  gdt
  lidt  idt
.endm

First-stage bootloader

Now that we’ve got all the required macros and functions out of the way, cobbling together the first-stage bootloader becomes simple. We basically turn the recipe presented at the start of this article into code, calling macros as necessary.

.code16
.intel_syntax noprefix
.text
.org 0x0

LOAD_SEGMENT = 0x1000  # 2nd stage loader will be loader into segment 1000h
FAT_SEGMENT  = 0x0ee0  # The boot disk's FAT will be loaded into segment 0x0ee0
# (9*512 bytes under 2nd stage loader, because the FAT
# consists of 9 512-byte segments).

.global main

main:
  jmp short start      # jump to beginning of code
  nop                  # Boot sector data starts 3 bytes from beginning, hence nop

.include "bootsector.s"
.include "macros.s"

start:
  mInitSegments                        # Initialize memory segments used by this program
  mResetDiskSystem                     # Reset the disk system
  mWriteString loadmsg                 # Display "loading..."
  mFindFile filename, LOAD_SEGMENT     # Find the 2ndstage file in the root directory
  mReadFAT FAT_SEGMENT                 # Load the FAT table into memory
  mReadFile LOAD_SEGMENT, FAT_SEGMENT  # Read the 2ndstage file into memory
  mStartSecondStage                    # Execute the 2ndstage file.

#
# Booting has failed because of a disk error.
# Inform the user and reboot.
#
bootFailure:
  mWriteString diskerror    # Show "Disk error, press key to reboot"
  mReboot                   # Reboot

.include "functions.s"

# PROGRAM DATA
filename:    .asciz "2NDSTAGEBIN"
rebootmsg:   .asciz "Press any key to reboot.rn"
diskerror:   .asciz "Disk error. "
loadmsg:     .asciz "Loading DevOS...rn"

root_strt:   .byte 0,0      # hold offset of root directory on disk
root_scts:   .byte 0,0      # holds # sectors in root directory
file_strt:   .byte 0,0      # holds offset of bootloader on disk

.fill (510-(.-main)), 1, 0  # Pad with nulls up to 510 bytes (excl. boot magic)
BootMagic:  .int 0xAA55     # magic word for BIOS

Second-stage bootloader

Now we can finally write the complete second-stage bootloader.

.code16
.intel_syntax noprefix
.text
.org 0x0

LOAD_SEGMENT = 0x2000   # load the kernel to segment 0x2000
FAT_SEGMENT  = 0x0ee0   # load FAT at segment 0x0ee0

.global main

main:
  jmp short start       # jump to beginning of code
  nop

# INCLUDES
.include "bootsector.s"
.include "functions.s"
.include "macros.s"
.include "a20.s"
.include "descriptors.s"

# PROGRAM DATA
filename:    .asciz "KERNEL  BIN"
rebootmsg:   .asciz "Press any key to reboot.rn"
diskerror:   .asciz "Disk error. "
a20error:    .asciz "A20 unavailable. "
root_strt:   .byte 0,0      # hold offset of root directory on disk
root_scts:   .byte 0,0      # holds # sectors in root directory
file_strt:   .byte 0,0      # holds offset of bootloader on disk
idt:
.word  2048  # Size of IDT (256 entries of 8 bytes)
.int   0x0   # Linear address of IDT
gdt:
.word  24    # Size of GDT: 3 entries of 8 bytes.
.int   2048  # Linear address of GDT

start:
  # Copy the boot sector to our code:
  mCopyBootSector
  # Find the kernel file:
  mFindFile filename, LOAD_SEGMENT
  # Load the kernel file into memory:
  mReadFile LOAD_SEGMENT, FAT_SEGMENT
  # Reset the disk system:
  mResetDiskSystem
  # Enable the A20 line:
  mEnableA20
  # Setup the interrupt descriptor table:
  mSetupIDT
  # Setup the global descriptor table:
  mSetupGDT
  # Actually load the IDT and GDT:
  mLoadDescriptorTables
  # Switch to protected mode:
  mGoProtected
  # Clear the prefetch queue:
  mClearPrefetchQueue
  # Point all data segments to GDT 2:
  mSetup386Segments
  # Jump to kernel code:
  mJumpToKernel
  # shouldn't get here...

#
# Booting has failed because of a disk error.
# Inform the user and reboot.
#
bootFailure:
  mWriteString diskerror
  mReboot

Summary

In this section of the “writing your own toy operating system” series, we’ve put together all the code we have written so far. The result is a first and second-stage bootloader that work together to load a kernel image, switch to protected mode, and run the kernel.

We haven’t actually gotten around yet to writing any kernel code, but in the source code that goes with this article there actually is a small kernel program that displays “Hello world”.

In the next section, we see about writing an actual kernel! Check back soon.