Welcome to 16892 Developer Community-Open, Learning,Share
menu search
person
Welcome To Ask or Share your Answers For Others

Categories

I learned to switch to protected mode with a simple DOS based bootloader. This loader loads kernel.bin into a buffer and copies the buffer to 100000h (kernel is 8KiB). Control is then transferred to the kernel. When I return from the kernel and attempt to switch to real mode I encounter a problem.

My FASM assembly code (Similar to my previous Stackoverflow question) is as follows:

format MZ
push cs
pop ds
mov eax,cs
shl eax,4
mov [AdresSegmentuProgramu_32],eax ;Calculating real mode segment
add eax,gdt_table
mov [gdtr+2],eax
mov ax,[AdresSegmentuProgramu_32+2]
mov [code_realsegment_descriptor+3],ax  
mov al,[AdresSegmentuProgramu_32+1]       ;Setting 16-bit descriptors to return from protected mode
    mov [code_realsegment_descriptor+2],al
    mov ax,[AdresSegmentuProgramu_32+2]
    mov [data_realsegment_descriptor+3],ax
mov al,[AdresSegmentuProgramu_32+1]
mov [data_realsegment_descriptor+2],al
mov ax,3d00h
mov dx,NazwaPliku
int 21h
mov bx,ax
mov ax,3f00h
mov cx,8192
mov dx,KernelGDOS32
int 21h
mov ax,3e00h
int 21h
lgdt [gdtr]

mov eax,[AdresSegmentuProgramu_32]

add eax, pmode_entry ;Far jump to reset CS and jump to simple code

mov [AdresSegmentu_PMODE_entry],eax

mov [far_jump],eax   
mov eax,[AdresSegmentuProgramu_32]   
add eax,KernelGDOS32   
mov [AdresSegmentu_KernelGDOS_32],eax

cli                         ; Turn off interrupts

mov eax,cr0

or eax,1    ;Switch to PMODE

mov cr0,eax

; Move code that was between turning on protectedmode bit and the FAR JMP   
; to an earlier point.  
; We need to do a FAR JMP but with a 32-bit offset and a 16-bit selector   
; rather than a 16-bit offset and 16-bit selector. A 16-bit offset will   
; not work for any address greater than 64KiB. Use FWORD modifier to allow   
; a 32-bit offset in the indirect address for the JMP FAR.
; FWORD = 48 bit address (32+16)

mov edi,[AdresSegmentu_KernelGDOS_32]

jmp far fword [ds:far_jump]

far_jump:   
dd 0
dw 08h ; Selector 0x08

gdtr: dw 128   
dd 0

ldtr:   
dw 0x3ff   
dd 0

AdresSegmentuProgramu_32 : dd 0
AdresSegmentu_PMODE_entry dd 0
AdresSegmentu_KernelGDOS_32 dd 0

NazwaPliku db 'kernel.bin',0
use32
align 4
gdt_table:
dq 0   ;NULL Descriptor
code_descriptor:
dw 0ffffh
dw 0                  ;8h
db 0
db 09ah
db 11001111b
db 0
data_descriptor: ;I prefer flat mode. There are two descriptors for data and code points to 0.
dw 0ffffh
dw 0
db 0                   ;10h
db 092h
db 11001111b
db 0
stack_descriptor:
dw 0ffffh
dw 0
db 0                      ;18h
db 096h
db 11001111b
db 0
code_realsegment_descriptor:
dw 0ffffh                      ;20h
dw 0
db 0
db 09ah
db 10001111b
db 0
data_realsegment_descriptor:
dw 0ffffh
dw 0
db 0
db 092h                           ;28h
db 10001111b
db 0
stack_realsegment_descriptor : dq 0
TIMES 8 dq 0
KernelGDOS32 : TIMES 8192 db 0 ;J?dro naszego systemu który zostanie za?adowany 
do obszaru pami?ci powy?ej 1 MB.
pmode_entry:

;this section works correctly

mov ebx,100000h
mov ax, 10h ;Set DS to a 32-bit data selector
mov ds, ax
mov ax,18h  ;Set SS to a 32-bit stack selector
mov ss,ax
mov esi,100000h
xor cx,cx
petla_glowna:
mov al,[edi]
mov [esi],al
inc esi
inc edi
cmp cx,8192
inc cx
jne petla_glowna

mov esp,200000h
call dword ebx

mov eax,0
mov cr3,eax

use16

;but i want to switch to real mode cpu generates protection fault
;I was reading osdev.org instructions and still nothing 

mov ax,0x28
mov ds,ax
mov es,ax   
mov fs,ax
mov gs,ax
mov ss,ax
mov sp,16000
jmp far 0x20:entry16
entry16:
mov eax,cr0
mov eax,0    ;back to real mode
mov cr0,eax

jmp dword 0:rmode   ;far jump
rmode:

mov sp,16000
mov ax,0
mov ds,ax
mov es,ax
mov fs,ax
mov es,ax
mov ss,ax

lidt [ldtr]
sti

mov ax,4c00h ;Exit process
int 21h
See Question&Answers more detail:os

与恶龙缠斗过久,自身亦成为恶龙;凝视深渊过久,深渊将回以凝视…
thumb_up_alt 0 like thumb_down_alt 0 dislike
1.8k views
Welcome To Ask or Share your Answers For Others

1 Answer

Observations of your code:

  • To disable paging clear bit 31 of CR0. It will be the kernel's responsibility to properly identity map the pages holding the GDT and the pages containing the instructions where the code transitions from protected mode to real mode.
  • The use16 should be after jmp far 0x20:entry16 and before the entry16 label. You have placed it too early in the code.
  • The entry16 label has to be fixed up (converted to a linear address) just like pmode_entry .
  • jmp dword 0:rmode uses a hard coded real mode segment of 0. This will cause problems since DOS likely didn't load your program at CS=0x0000. You need to store the original CS segment register before entering protected mode so you can use it to perform a FAR JMP (or equivalent) with the proper real mode segment.
  • You hard code the SP to 16000. You should be saving the original SS:SP and restoring them to their previous values after returning back to real mode. Address 16000 could be in the middle of memory used by DOS. This could lead to corruption.

This code is an adaptation of some code I wrote for a question posed on the #OSDev IRC channel. It incorporates your idea of loading kernel.bin using DOS int 21h and copying it to memory beyond 0x100000. I put the kernel at 0x110000 in the event that DOS is using the memory between 0x100000 and 0x10FFEF as the DOS High Memory Area (HMA).

; Assemble to pmdos.exe using FASM with:
;     fasm pmdos.asm

format MZ

STACK32_TOP  EQU 0x200000
KERNEL_START EQU 0x110000
KERNEL_SIZE  EQU 8192

use16
main:
    push cs
    pop ds                      ; DS=CS

    ; Read KERNEL.BIN into 8kb buffer
    mov ah, 0x3d
    mov dx, kernel_file
    int 0x21                    ; Open KERNEL.BIN
    mov bx, ax                  ; BX = file handle
    jnc .read                   ; No Error? Read file

    mov dx, file_not_fnd        ; Print an error and exit back to DOS
    mov ah, 0x9
    int 0x21                    ; Print Error
    jmp exit

.read:
    mov ah, 0x3f                ; Read file
    mov cx, KERNEL_SIZE         ; Maximum 8192 bytes
    mov dx, kernel_mem          ; Buffer to read into
    int 0x21
    jnc .close                  ; No Error? Finished, close file

    mov dx, file_read_err       ; Print an error and exit back to DOS
    mov ah, 0x9
    int 0x21                    ; Print Error
    jmp exit

.close:
    mov ah, 0x3e                ; Close file
    int 0x21

    call check_pmode            ; Check if we are already in protected mode
                                ;    This may be the case if we are in a VM8086 task.
                                ;    EMM386 and other expanded memory manager often
                                ;    run DOS in a VM8086 task. DOS extenders will have
                                ;    the same effect

    jz not_prot_mode            ; If not in protected mode proceed to switch
    mov dx, in_pmode_str        ;    otherwise print an error and exit back to DOS
    mov ah, 0x9
    int 0x21                    ; Print Error
    jmp exit                    ; Exit program

not_prot_mode:
    call a20_on                 ; Enable A20 gate (uses Fast method as proof of concept)
    cli                         ; Disable interrupts

    ; Compute linear address of label gdt_start
    ; Using (segment SHL 4) + offset
    mov eax, cs                 ; EAX = CS
    shl eax, 4                  ; EAX = (CS << 4)
    mov ebx, eax                ; Make a copy of (CS << 4)
    add [gdtr+2], eax           ; Add base linear address to gdt_start address
                                ;     in the gdtr
    lgdt [gdtr]                 ; Load gdt

    ; Compute linear address of labels using (segment << 4) + offset.
    ; EBX already is (segment << 4). Add it to the offsets of the labels to
    ; convert them to linear addresses
    lea edi, [pm16_entry+ebx]   ; EDI = 16-bit protected mode entry (linear address)
    lea esi, [kernel_mem+ebx]   ; ESI = Kernel memory buffer (linear address)
    add ebx, code_32bit         ; EBX = code_32bit (linear address)

    push ds                     ; Save real mode segments on real mode stack
    push es
    push fs
    push gs
    mov ecx, cs                 ; ECX = DOS real mode code segment

    push dword CODESEL32        ; CS = 32-bit PM code selector
    push ebx                    ; Linear offset of code_32bit
    mov bp, sp                  ; m16:32 address on top of stack, point BP to it

    mov eax, cr0
    or eax, 1
    mov cr0, eax                ; Set protected mode flag
                                ; We are in quasi 16-bit protected mode at this point
    ; JMP to 32-bit protected mode
    jmp far fword [bp]          ; Indirect m16:32 FAR jmp with
                                ;    m16:32 constructed at top of stack
                                ;    DWORD allows us to use a 32-bit offset in 16-bit code

; 16-bit functions that run in real mode

; Check if protected mode is enabled, effectively checking if we are
; in in a VM8086 task. Set ZF to 1 if in protected mode

check_pmode:
    smsw ax
    test ax, 0x1
    ret

; Enable a20 (fast method). This may not work on all hardware
a20_on:
    cli
    in al, 0x92                 ; Read System Control Port A
    test al, 0x02               ; Test current a20 value (bit 1)
    jnz .skipfa20               ; If already 1 skip a20 enable
    or al, 0x02                 ; Set a20 bit (bit 1) to 1
    and al, 0xfe                ; Always write a zero to bit 0 to avoid
                                ;     a fast reset into real mode
    out 0x92, al                ; Enable a20
.skipfa20:
    sti
    ret

; 16-bit protected mode entry point and code
pm16_entry:
    mov ax, DATASEL16           ; Set all data segments to 16-bit data selector
    mov ds, ax
    mov es, ax
    mov fs, ax
    mov gs, ax
    mov ss, ax

    mov eax, cr0                ; Disable protected mode
    and eax, NOT 0x80000001     ; Disable paging (bit 31) and protected mode (bit 0)
                                ; The kernel will have to make sure the GDT is in
                                ;     a 1:1 (identity mapped page) as well as lower memory
                                ;     where the DOS program resides before returning
                                ;     to us with a RETF
    mov cr0, eax

    push cx                     ; Return to the real_mode code
    push real_mode_entry        ;     with the original CS value (in CX)
    retf

; 16-bit real mode entry point
real_mode_entry:
    xor esp, esp                ; Clear all bits in ESP
    mov ss, dx                  ; Restore the real mode stack segment
    lea sp, [bp+8]              ; Restore real mode SP
                                ; (+8 to skip over 32-bit entry point and Selector that
                                ;     was pushed on the stack in real mode)
    pop gs                      ; Restore the rest of the real mode data segment
    pop fs
    pop es
    pop ds
    lidt [idtr]                 ; Restore the real mode interrupt table
    sti                         ; Enable interrupts

exit:
    mov ax, 0x4c00              ; Return to DOS with value 0
    int 0x21

; Code that will run in 32-bit protected mode
;
; Upon entry the registers contain:
;     EDI = 16-bit protected mode entry (linear address)
;     ESI = Kernel memory buffer (linear address)
;     EBX = code_32bit (linear address)
;     ECX = DOS real mode code segment

align 4
use32

code_32bit:
    mov ebp, esp                ; Get current SS:ESP
    mov edx, ss

    cld                         ; Direction flag forward
    mov eax, DATASEL32          ; Set protected mode selectors to 32-bit 4gb flat
    mov ds, ax
    mov es, ax
    mov fs, ax
    mov gs, ax
    mov ss, ax
    mov esp, STACK32_TOP        ; Should set ESP to a usable memory location
                                ; Stack will be grow down from this location

    ; Build linear address and selector on stack for RETF to return to
    push CODESEL16              ; Put 16-bit protected mode far entry point 0x18:pm16_entry
    push edi                    ;     on stack as a return address (linear address)

    push edx                    ; Save EDX, EBP, ECX
    push ebp
    push ecx

    mov edi, KERNEL_START       ; EDI = linear address where PM code will be copied
    mov ecx, KERNEL_SIZE        ; ECX = number of bytes to copy
    rep movsb                   ; Copy all code/data from kernel buffer to KERNEL_START
    call CODESEL32:KERNEL_START ; Absolute jump to relocated code

    pop ecx                     ; ECX = Real mode code segment
    pop ebp                     ; Recover old SS:SP into EDX:EBP
    pop edx
    retf                        ; Switch to 16-bit protected mode, goto pm16_entry

kernel_file:   db "kernel.bin", 0
file_not_fnd:  db "KERNEL.BIN not found - exiting", 0x0a, 0x0d, "$"
file_read_err: db "Can't read KERNEL.BIN - exiting", 0x0a, 0x0d, "$"
in_pmode_str:  db "Processor already in protected mode - exiting", 0x0a, 0x0d, "$"

align 4
; Real mode interrupt vector table (IDTR)
idtr:
    dw 0x3ff
    dd 0

align 4
gdtr:
    dw gdt_end-gdt_start-1
    dd gdt_start

align 4
gdt_start:
    ; First entry is always the Null Descriptor
    dd 0
    dd 0

gdt_code:
    ; 32-bit 4gb flat r/w/executable code descriptor
    dw 0xFFFF                   ; limit low
    dw 0                        ; base low
    db 0                        ; base middle
    db 10011010b                ; access
    db 11001111b                ; granularity
    db 0                        ; base high

gdt_data:
    ; 32-bit 4gb flat r/w data descriptor
    dw 0xFFFF                   ; limit low
    dw 0                        ; base low
    db 0                        ; base middle
    db 10010010b                ; access
    db 11001111b                ; granularity
    db 0                        ; base high

gdt16_code:
    ; 16-bit 4gb flat r/w/executable code descriptor
    dw 0xFFFF                   ; limit low
    dw 0                        ; base low
    db 0                        ; base middle
    db 10011010b                ; access
    db 10001111b                ; granularity
    db 0                        ; base high

gdt16_data:
    ; 16-bit 4gb flat r/w data descriptor
    dw 0xFFFF                   ; limit low
    dw 0                        ; base low
    db 0                        ; base middle
    db 10010010b                ; access
    db 10001111b                ; granularity
    db 0                        ; base high
gdt_end:

CODESEL32 = gdt_code - gdt_start
DATASEL32 = gdt_data - gdt_start
CODESEL16 = gdt16_code - gdt_start
DATASEL16 = gdt16_data - gdt_start

kernel_mem: TIMES KERNEL_SIZE db 0x0

In order for the kernel to return when finished you must use an RETF (Far return) instruction. A sample kernel.asm file that prints some letters on the display and returns could look something like:

; Assemble to kernel.bin using FASM with:
;     fasm kernel.asm

format binary

VIDEO_MEM EQU 0x0b8000

org 0x110000                    ; Set ORG to address kernel is loaded at
use32
kernel_entry:
    ; Write MDP in w

与恶龙缠斗过久,自身亦成为恶龙;凝视深渊过久,深渊将回以凝视…
thumb_up_alt 0 like thumb_down_alt 0 dislike
Welcome to 16892 Developer Community-Open, Learning and Share
...