CLOSE

Hello everyone! As you may know, in real mode, only the first 1 MB of memory is addressable using the segment:offset addressing scheme with 16-bit registers. Now, suppose we want to load a file—like the stage 2 of a bootloader—that exceeds 1 MB in size. At first, it might seem like there's no issue since modern systems have gigabytes of RAM. However, in real mode, we are restricted and cannot directly access memory beyond the 1 MB boundary. So, how can we load a file larger than 1 MB while operating in real mode?

So there is a work around for it, which we will discuss in this article.

Work Around to Load File of Size Greater than 1MB in Real Mode

In real mode, memory access is restricted to the first 1 MB of memory due to the 20-bit address limitation of the segment:offset addressing scheme. This can be a challenge if you need to load a file (such as stage 2 of a bootloader) that exceeds 1 MB. However, there are workarounds to overcome this limitation:

1️⃣ Use the High Memory Area (HMA)

Although real mode restricts access to 1 MB, you can access an additional 64 KB above the 1 MB mark (from 0x100000 to 0x10FFFF) using the A20 gate. The A20 line allows the CPU to use the 21st address line, effectively enabling access to this small additional memory area.

Here's how it works:

  • Enable the A20 line programmatically.
  • Use segment:offset addressing to access the memory in the high memory area.

Technically speaking this won't help much as most of the address space is reserved in that 1 MB of real mode and it is scattered too

2️⃣ Unreal Mode (Flat Real Mode)

Flat real mode (or unreal mode) is another workaround that involves tweaking the CPU’s segment registers to allow access to memory beyond 1 MB while still technically operating in real mode. Steps include:

  1. Enable the A20 line
  2. Switch briefly to protected mode.
  3. Reconfigure the segment descriptors to expand the accessible address range.
  4. Return to real mode while keeping the updated descriptors.

This approach provides extended memory access while remaining compatible with real-mode operations. Means we can make use of real mode interrupts.

Implementing Unreal Mode

Let's understand the step-by-step process of implementing unreal mode to load second stage at higher memory.

1 Set up Environment

Before transitioning to unreal mode, you must have the stage 2 file all set up, like for the binary format you must specify its origin with ORG directive to specify where it would be loaded in memory which is necessary for getting the offset of the declared variables.

2 Set up stack

Next thing is to set up the stack for the function calls.

2 Enable the A20 line

Well there are various ways to enable the A20 line. Below is the code which enables it using the keyboard a20 gate:

; Enable the A20 gate
; This code is responsible for enabling the A20 line, which allows access to memory 
; above 1MB in real mode (a requirement for protected mode or extended memory).

enableA20:
	call	_a20_loop           ; Check if the A20 line is already enabled.
	jnz		_enable_a20_done   ; If A20 is enabled, skip further steps.

	; Send command 0xD1 to the keyboard controller (port 0x64).
	; 0xD1 instructs the controller to write a value to the output port.
	mov		al, 0xd1
	out		0x64, al

	call	_a20_loop           ; Wait for the keyboard controller to be ready.
	jnz		_enable_a20_done   ; If the operation is complete, skip further steps.

	; Send the value 0xDF to the keyboard controller's output port (port 0x60).
	; This sets bit 1 (A20 line enable) while preserving other bits.
	mov		al, 0xdf
	out		0x60, al

_a20_loop:
	; Poll the keyboard controller until it's ready or a timeout occurs.
	mov		ecx, 0x20000        ; Set a timeout counter (approximately 2^17 iterations).
_loop2:
	jmp		short _c           ; Jump to the inner polling loop.
_c:
	in		al, 0x64           ; Read the keyboard controller status byte from port 0x64.
	test	al, 0x2            ; Check if bit 1 (input buffer full) is set.
	loopne	_loop2             ; Repeat until the input buffer is clear or timeout.

_enable_a20_done:
	; A20 line is enabled or the timeout occurred.
	ret                     ; Return from the subroutine.

3 Load the 32-bit GDT

The GDT (Global Descriptor Table) contains the descriptors that define memory segments. Each descriptor is an 8-byte structure. For unreal mode, we would need at least two descriptor.

gdt:
    ; the first entry serves 2 purposes: as the GDT header and as the first descriptor
    ; note that the first descriptor (descriptor 0) is always a NULL-descriptor
    ; descriptor 0
    db 0xFF        ; full size of GDT used
    db 0xff        ;   which means 8192 descriptors * 8 bytes = 2^16 bytes
    dw gdt         ;   address of GDT (dword)
    dd 0
    ; descriptor 1:
    dd 0x0000ffff  ; base - limit: 0 - 0xfffff * 4K
    dd 0x008f9a00  ; type: 16 bit, exec-only conforming, <present>, privilege 0
    ; descriptor 2:
    dd 0x0000ffff  ; base - limit: 0 - 0xfffff * 4K
    dd 0x008f9200  ; type: 16 bit, data read/write, <present>, privilege 0
 

4 Enable the protection bit for Protected Mode

In order to enable the protected mode, we have to enable the protection bit in the special register which is CR0.

    ;; Enable protection bit for protected mode
    mov eax, cr0
    or al, 0x1
    mov cr0, eax

5 Jump to 32 bit land

Now we have enabled the protected mode, but we have to far jump into the protected land. We have to jump into the code segment as per the GDT, and Code segment in the GDT is at offset 0x8 (8 in decimal) so jump relative to the newly set upGDT.

;; Jump to 32-bit land
    jmp dword 0x8: unreal32

6 Set up segment register in 32-bit land

Once we entered into the protected mode. We have to set up the segment register to look for the gdt entry. Here we initialize them by 0x10 which is 16 in the decimal and it is the offset of the Data Segment in the GDT

;; Set up segment registers
    mov bx, 0x10
    mov ds, bx
    mov es, bx
    mov ss, bx

7 Disable the protection bit, for unreal mode

Now disable the protection bit to disable the protected mode.

;; Disable protection bit, to jump back for the unreal mode
    and al, 0xfe
    mov cr0, eax

8 Jump back to 16-bit mode, which would be unreal mode

Now jump back to the real mode.

;; Jump to unreal mode
jmp 0x7c0:unreal - 0x7c00

9 Use the disk read interrupt function to load the stage 2 at higher memory

;; Load the second stage to 0x100000
    mov ax, 0x1000          ; Load segment address 0x1000 (for 0x100000)
    mov es, ax              ; Set ES to 0x1000
    mov ah, 0x02            ; BIOS disk read function
    mov al, 2               ; Number of sectors to read
    mov ch, 0               ; Cylinder 0
    mov cl, 3               ; Sector number (1-based indexed)
    mov dh, 0               ; Head 0
    mov dl, [boot_disk_number] ; Drive number (HDD = 0x80, Floppy = 0x00)
    mov bx, 0x0000          ; Offset 0x0000
                            ; Read at [es:offset]
    int 0x13                ; BIOS call to read sector
    jc diskReadFailure      ; Check for errors, if carry flag is set, means failure

10 Jump to stage 2

; Jump to stage 2
jmp 0x1000:0x0000       ; Far jump to 0x100000


;; OR

; Unreal Mode allows access to this area, but we must set up registers carefully
push 0x1000             ; Push the high 16 bits (segment base) of 0x100000
push 0x0000             ; Push the offset within that segment (0x0)
retf

jmp $

11 Stage2

BITS 16

ORG 0x100000  ; Logical address at 0x100000 (physical: 0x1000:0x0000)

stage2_entry:
    ;; Set up data segment
    ;; It is important 
    mov ax, 0x1000       ; Set data segment to 0x1000
    mov ds, ax
    
    mov ah, 0x0e
    mov al, 'M'
    int 0x10
    
    ;; Print the stage 2 welcome message
    mov si, stage2Msg
    call print

jmp $    ; Infinite loop to halt execution


; Function to print a newline
newline:
    pusha                ; Save all registers
    mov ah, 0x0e         ; BIOS teletype function
    mov al, 0x0D         ; Carriage Return
    int 0x10             ; Print it
    mov al, 0x0A         ; Line Feed
    int 0x10             ; Print it
    popa                 ; Restore all registers
ret

; prints message in register si
print:
    pusha
    .loopy:
        lodsb
        or al, al
        jz .done
        mov ah, 0x0e
        mov bx, 7
        int 0x10
        jmp .loopy
    .done:
        call newline
    popa
ret


times 512 - ($ - $$) db 0    ; (Padded to 512 bytes - 1 sector)


;; Data Area
stage2Msg: db "Welcome to Stage2", 0

times 1024 - ($ - $$) db 0    ; (Padded to 1 KB - 2 Sectors)