Bootsector bug

Question about which tools to use, bugs, the best way to implement a function, etc should go here. Don't forget to see if your question is answered in the wiki first! When in doubt post here.
Post Reply
suslik
Member
Member
Posts: 45
Joined: Sun May 27, 2012 1:00 am
Location: Russia

Bootsector bug

Post by suslik »

I've write a simple boosector that switches CPU to Unreal mode and loads a kernel at address 0x100000. To load a kernel it uses BIOS int 0x13 AH=0x42 (LBA28). All works fine on BOCHS but real PC hangs (it is not rebooted - only hangs). I've investigated the problem and found out that PC hangs at code that copies the first loaded sector to extended memory (see the "load_sectors" function).

So, I suspect a code that turns on the A20: A20 remains turned off, first kernel sector destructs IVT and first interrupt cause exception and PC hangs... But I'm testing A20 - all is fine :(

P.S: I've also tried to turn on A20 by means of kbd controller - nothing change... I've commented this code to free some bytes for debug printing.

Whole code:

Code: Select all

;------------------------------------------------------------------------------
;                            Bootsector (512 bytes)
;     (all kernel bootloader is fit into 512 bytes of the bootsector)
;
; Loads kernel from disk using BIOS int 0x13 ah=0x42 (LBA). Compliant to
; boot_agreements.txt.
;
; NOTE: You must fit into 512 bytes so you must think about the length of
; every command you use. If accidently you don't fit - ask assembler to generate
; listing where you can see all opcodes and replace some commands with shorter ones
; (especially pay attention to JMP, JC, JNE, ... : it is nice when you use short form
; of JMP. REMEMBER: always tell NASM explicity that you want SHORT jump)
;------------------------------------------------------------------------------

; Kernel header:
; offset 0: magic number
; offset 4: kernel size in bytes
; offset 8: kernel uninitialized data size in dwords
; offset 12: kernel stack size in bytes
; offset 16: kernel entry address

%define KERNEL_START_SECTOR 1

; Here we must load kernel (after the first megabyte)
%define KERNEL_START 0x100000

; Disk sector size
%define SECTOR_SIZE 512
%define SECTOR_SIZE_BITS 9

; Here BIOS loads boot sector
%define BOOTSECTOR_START 0x7C00

%define BOOTSECTOR_STACK_SIZE 8192
%define BOOTSECTOR_SP (BOOTSECTOR_START + SECTOR_SIZE + BOOTSECTOR_STACK_SIZE)

%define MAGIC_NUMBER 0x23E9

%macro PRINT 1
;	push si
	mov si, %1
	call puts
;	pop si
%endmacro

[map symbols bootsect.map]

ORG BOOTSECTOR_START

[BITS 16]

start:
	; IMPORTANT: All bootloader code is sutiated in the first
	; segment (0 - 64KB), so DS and SS must holds zeroes.
	xor ax, ax
	mov ds, ax
	
	; Switch to our stack (you don't have to disable interrupts since 80386 do this for you: 80386
	; disable interrupts when it executes "mov ss, ax" and enables them after "mov sp, ...")
	; See [9.2.4  MOV or POP to SS Masks Some Interrupts and Exceptions] of INTEL 80386 PROGRAMMER'S
	; REFERENCE MANUAL 1986
	mov ss, ax
	mov sp, BOOTSECTOR_SP
	
	; PRINT (msg_hello)
	
	; The BIOS places the boot drive number in DL before gives control to us
	; 0 - 1st floppy, 1 - 2nd floppy, 0x80 - 1st drive, 0x81 - 2nd drive, ...
	; We must save this value so we can read our kernel from the right drive
	xor dh, dh
	push dx
	
	; Determine RAM size in 1 KB blocks in the range 0x0000 - 0xA0000 (minus EBDA size)
	xor ax, ax
	int 0x12 ; return interested RAM size in AX (always <= 640 KB)
	; At the very beginning of the low memory is situated IVT (1 KB)
	; and right after it - BDA (256 bytes), so if we want to switch
	; to the real mode again in future we must not corrupt memory
	; range from 0x0000 to 0x0500.
	jc determ_mem_err
	push ax
	
	; Determine extended RAM size
	; AX = RAM size in 1 KB blocks in the range 0x100000 - 0xFFFFFF (<= 15MB);
	; BX = RAM size in 64 KB blocks in the range 0x1000000 - 0x???????
	mov ax, 0xE801
	int 0x15
	jc determ_mem_err
	push ax
	push bx
	
	; Variables in stack:
	; sp    -> RAM size in 64 KB blocks in the range 0x1000000 - 0x???????
	; sp+2  -> RAM size in 1 KB blocks in the range 0x100000 - 0xFFFFFF
	; sp+4  -> RAM size in 1 KB blocks in the range 0x0000 - 0xA0000 (minus EBDA size)
	; sp+6  -> HDD kernel has loaded from
	
	; BP - points to the variables in stack
	mov bp, sp
	
;------------ Switch CPU to "unreal mode"--------------------------------------
	
switch_to_unreal:
	cli
	
	lgdt [gdtr] ; LGDT loads only low 24 bits of GDT base when operand is 16-bit!
	
	push ds
	push es
	
	mov eax, cr0
	or al, 1
	mov cr0, eax
		
	mov bx, DATA_SEG_DESC_SEL
	mov ds, bx
	mov es, bx
	
	and al, 0xFE
	mov cr0, eax
	
	pop es
	pop ds
	
	sti
	
;--------------------Enable A20------------------------------------------------
; DS and ES already has 0-offset base and 4GB-limit
	
	PRINT (msg_test_a20)
	
	;call test_a20
	;jnc short load_kernel
	
	in al, 0x92
	or al, 2
	out 0x92, al
	
	;call kbd_enable_a20
	
	; You should set a timeout and check A20 until this timeout is elapsed,
	; since 8042 needs some time to turn on the A20
	
	; Set 1 sec timeout by means of RTC 
	; INT 0x15, AH=0x83, AL=0 - Set/Cancel Wait Interval
	; CX:DX - wait interval in microseconds
	; ES:BX -> byte whose high bit is to be set at end of interval
	;mov ah, 0x83
	;xor al, al
	; 1000000 us = 0xF4240
	;mov cx, 0x000F
	;mov dx, 0x4240
	;mov bx, BOOTSECTOR_START + SECTOR_SIZE - 1 ; points to 0xAA
	;and byte [bx], 01111111b
	;int 0x15

check_a20:
	call test_a20
	jnc short load_kernel
	;test byte [bx], 10000000b
	;jz check_a20
	jmp short a20_fault

;------------------------------------------------------------------------------
	
err:
;	jmp $
	cli
	hlt

determ_mem_err:
	PRINT(msg_determ_mem_err)
	jmp short err

a20_fault:
	PRINT(msg_a20_err)
	jmp short err

invalid_magic:
	PRINT(msg_invalid_magic)
	jmp short err

read_err:
	PRINT(msg_read_err)
	jmp short err

no_lba:
	PRINT(msg_no_lba)
	jmp short err
	
;-------------- Load kernel----------------------------------------------------
load_kernel:
	
	; Check if BIOS know about LBA
	mov ah, 0x41
	mov bx, 0x55AA
	mov dl, [bp+6]
	int 0x13
	jc short no_lba
	
	;PRINT (msg_load_kernel)
	
; DS and ES already has 0-offset base and 4GB-limit
loading_kernel:
	
	; Load the first kernel sector
	mov dl, [bp+6] ; Drive number
	mov cx, 1 ; Sectors count
	; ES:EDI - buffer
	xor ax, ax
	mov es, ax
	mov edi, KERNEL_START
	mov eax, KERNEL_START_SECTOR
	call load_sectors
	jc short read_err
	
	; Check magic number
	cmp word [dword KERNEL_START], MAGIC_NUMBER
	jne short invalid_magic
	
	mov ecx, [dword KERNEL_START + 4] ; ECX - kernel size in bytes
	; Compute kernel size in sectors: (ksize + SECTOR_SIZE - 1) / SECTOR_SIZE
	add ecx, SECTOR_SIZE - 1
	shr ecx, SECTOR_SIZE_BITS ; CX - kernel size in sectors
	; Zero kernel size is treated as 65536 sectors
	dec cx
	jz short kernel_has_loaded
	
	; Load the rest sectors
	mov eax, KERNEL_START_SECTOR + 1 ; Start sector
	call load_sectors
	jc short read_err
	
kernel_has_loaded:

;----------------Switch to protected mode--------------------------------------

switch_to_protected:

	PRINT (msg_switch_to_protected)
	
	; TURN OFF INTERRUPTS !!!
	cli
	
	; Load GDT register (we has already loaded it when we switched to the unreal
	; mode)
	; lgdt [gdtr]
	
	; Set PE (Protected Enabled) bit in CR0
	mov eax, cr0
	or al, 1
	mov cr0, eax

	; Do long jump to load code segment selector to the CS
	jmp CODE_SEG_DESC_SEL:protected

;------------------------------------------------------------------------------

[BITS 32]

; We jump here right after we switch CPU to the 32-bit Protected Mode
protected:
	; Load into DS, ES, FS, GS, SS data segment selector
	mov ax, DATA_SEG_DESC_SEL
	mov ds, ax
	mov es, ax
	mov ss, ax
	mov fs, ax
	mov gs, ax
	
	; Fill the kernel uninitialized data with zeroes
	; ES:EDI points to the uninitialized data start
	mov edi, [KERNEL_START + 4] ; kernel size in bytes
	add edi, KERNEL_START ; EDI - uninitialized data start
	mov ecx, [KERNEL_START + 8] ; ECX - uninitialized data size in dwords
	xor eax, eax
	cld
	rep stosd
	
	; Now EDI points right after the uninitialized data
	add edi, [KERNEL_START + 12] ; Add stack size
	; Switch to the kernel stack
	mov esp, edi
	
	; Push to kernel stack address of the struct with collected data
	movzx ebp, bp
	push ebp
	
	PRINT (msg_jmp_to_kernel_entry)
	
	jmp [KERNEL_START + 16] ; kernel entry

;------------------------------------------------------------------------------

; The Global Descriptor Table
gdt:
	; zero descriptor
	db 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00
CODE_SEG_DESC_SEL equ $-gdt
	; code segment descriptor, DPL=0, base=0, limit=4GB
	db 0xFF, 0xFF, 0x00, 0x00, 0x00, 0x9A, 0xCF, 0x00
DATA_SEG_DESC_SEL equ $-gdt
	; data segment descriptor, DPL=0, base=0, limit=4GB
	db 0xFF, 0xFF, 0x00, 0x00, 0x00, 0x92, 0xCF, 0x00
gdt_end:

; GDTR value
gdtr:
	dw gdt_end - gdt - 1
	dd gdt

;------------------------------------------------------------------------------

[BITS 16]

; Enable A20 Gate by means of keyboard controller on motherboard - Intel 8042
; Destroy AL 
;kbd_enable_a20:
;	cli
;	call wait_8042
;	mov al, 0xD1
;	out 0x64, al
;	call wait_8042
;	mov al, 0xDF
;	out 0x60, al
;	call wait_8042
;	sti
;	ret

;wait_8042:
;	in al, 0x61 ; short delay
;	in al, 0x64 ; Read Status register of 8042
;	test al, 2 ; Zero bit 2 of Status register indicates that input buffer
;	           ; of 8042 is empty (i.e. it has eaten the byte we've write
;	           ; into)
;	jnz wait_8042
;	ret

; Fast method of A20 enabling (only on PS/2)
; in al, 0x92
; or al, 2
; out 0x92, al

%define BOOTSECTOR_MAGIC_WORD 0xAA55

test_a20:
	mov esi, BOOTSECTOR_START + SECTOR_SIZE - 2 ; ESI - points to the
	                                           ; last bootsector word
	                                           ; it is equal to 0xAA55
	cmp word [esi + 0x100000], BOOTSECTOR_MAGIC_WORD
	jne .m1
	neg word [esi]
	cmp word [esi + 0x100000], ~BOOTSECTOR_MAGIC_WORD
	jne .m1
	stc
	ret
.m1:
	clc
	ret

; Print string DS:SI points to. After all DS:SI will point right after the
; string ending zero. Destruct AX.
puts:
	cld
.loop:
	lodsb
	test al, al
	jz .quit
	mov ah, 0xE
	int 0x10
	jmp short .loop
.quit:
	ret

; BIOS int 0x13 ah=0x42 (LBA) The Disk Address Packet Structure
align 8
DataAddressPacket:
	db 16 ; struct size (always 16 bytes)
	db 0 ; reserved (always 0)
DataAddressPacket.SectorsCount:
	dw 0 ; sector count to read. On some BIOS-es you can specify only up to
	     ; 127 sectors. BIOS int 0x13 places here number of sectors actually
	     ; read
DataAddressPacket.BufferOffset:
	dw 0 ; buffer offset
	dw 0 ; buffer segment
DataAddressPacket.StartSector:
	dd 0 ; sector number to read
	dd 0 ; used only in LBA48

; Load sectors from the drive by means of BIOS INT 0x13 AH=0x42 (you must check
; byself if this function is supported by BIOS) Input: DL - drive index, EAX -
; start sector, CX - sectors count, ES:EDI - pointer to the buffer (not ES:DI
; since it is intended to load into the extended memory. To do this switch CPU
; to the unreal mode!) Return: OK - carry flag is off, read error - carry flag
; is on, CX - number of read sectors, EDI points to the next byte after buffer.
; AH is corrupted.

load_sectors:
	push esi
	push bx
	
	xor bx, bx ; BX - number of read sectors
	
	; Reserve space in stack for buffer
	sub sp, SECTOR_SIZE
	
	mov word [DataAddressPacket.BufferOffset], sp
	mov dword [DataAddressPacket.StartSector], eax ; Now we can use EAX
	
.load_sector:
	
	; Restore sectors count to read int 0x13 ah=0x42 write to this field the
	; number of successfully readed sectors
	mov word [DataAddressPacket.SectorsCount], 1
	
	; ds:si must point to DAP
	mov si, DataAddressPacket
	
	mov ah, 0x42
	int 0x13
	jc .read_err
	
	;PRINT (msg_sector_loaded); <-- Prints when uncommented
	
	; Copy sector from buffer to its destination
	; ds:esi -> es:edi
	xor esi, esi
	mov si, sp
	push cx
	mov ecx, SECTOR_SIZE >> 2
	cld
	a32 rep movsd
	pop cx
	
	PRINT (msg_sector_loaded); <-- Never prints
	
	inc bx
	cmp bx, cx
	je .all_loaded
	
	; Increase LBA address to read
	inc dword [DataAddressPacket.StartSector]
	jmp short .load_sector
	
.all_loaded:
	clc
.read_err:
	mov cx, bx
	; Free buffer (don't use ADD since we must preserve Carry Flag!)
	mov bx, sp
	lea sp, [bx + SECTOR_SIZE]
	pop bx
	pop esi
	ret
		
msg_read_err: db "RE", 0 ; Disk read error
msg_no_lba: db "LBA", 0 ; BIOS knows nothing about LBA
msg_determ_mem_err: db "MEM", 0 ; Determining available memory error
msg_invalid_magic: db "MAGIC", 0 ; Invalid magic number
msg_a20_err: db "A20", 0 ; A20 enabling error
msg_hello: db "H", 0 
msg_test_a20: db "A", 0
msg_load_kernel: db "L", 0
msg_sector_loaded: db "S", 0
msg_switch_to_protected: db "P", 0
msg_jmp_to_kernel_entry: db "J", 0


; Boot sector signature
TIMES 510 - ($ - $$) db 0
db 0x55, 0xAA
User avatar
Combuster
Member
Member
Posts: 9301
Joined: Wed Oct 18, 2006 3:45 am
Libera.chat IRC: [com]buster
Location: On the balcony, where I can actually keep 1½m distance
Contact:

Re: Bootsector bug

Post by Combuster »

... ES already has 0-offset base and 4GB-limit
That's rather unlikely at that point.
"Certainly avoid yourself. He is a newbie and might not realize it. You'll hate his code deeply a few years down the road." - Sortie
[ My OS ] [ VDisk/SFS ]
Antti
Member
Member
Posts: 923
Joined: Thu Jul 05, 2012 5:12 am
Location: Finland

Re: Bootsector bug

Post by Antti »

Code: Select all

   mov ah, 0x42
   int 0x13
   jc .read_err

   ;PRINT (msg_sector_loaded); <-- Prints when uncommented
   
   ; Copy sector from buffer to its destination
   ; ds:esi -> es:edi
   xor esi, esi
   mov si, sp
   push cx
   mov ecx, SECTOR_SIZE >> 2
   cld
   a32 rep movsd
   pop cx
   
   PRINT (msg_sector_loaded); <-- Never prints
It may be that the int 0x13 call trashes the edi register.

Code: Select all

   push edi        ; Added by Antti
   mov ah, 0x42
   int 0x13
   jc .read_err
   pop edi          ; Added by Antti
User avatar
trinopoty
Member
Member
Posts: 87
Joined: Wed Feb 09, 2011 2:21 am
Location: Raipur, India

Re: Bootsector bug

Post by trinopoty »

Try enabling A20 before switching to Unreal mode.
Also, try doing a manual copy instead of 'a32 rep movsd'
suslik
Member
Member
Posts: 45
Joined: Sun May 27, 2012 1:00 am
Location: Russia

Re: Bootsector bug

Post by suslik »

To Combuster: When switching to Unreal mode I load to ES selector of data segment descriptor with base=0, limit=4GB:
mov bx, DATA_SEG_DESC_SEL
mov ds, bx
mov es, bx
To Antti: nothing change when I add push/pop edi. I've checked INT 0x13 AH=0x42 in Ralf Brown's Interrupt List and found nothing about EDI distruction.

To trinopoty: your advice looks like a bit of voodoo. I try to avoid what I can't understand when I'm developing my system. Can you explain your idea?
suslik
Member
Member
Posts: 45
Joined: Sun May 27, 2012 1:00 am
Location: Russia

Re: Bootsector bug

Post by suslik »

To Antti: I'm sorry, I hurried and made some typos when I checked your advice. Now I fixed them... and everything works fine! You were absolutely right - INT 0x13 doesn't preserve high half of EDI. Thank you a lot - I would not find out this fact by myself.
Antti
Member
Member
Posts: 923
Joined: Thu Jul 05, 2012 5:12 am
Location: Finland

Re: Bootsector bug

Post by Antti »

suslik wrote:I've checked INT 0x13 AH=0x42 in Ralf Brown's Interrupt List and found nothing about EDI distruction.
suslik wrote:Now I fixed them... and everything works fine! You were absolutely right - INT 0x13 doesn't preserve high half of EDI. Thank you a lot - I would not find out this fact by myself.
As a general rule of thumb, I have always assumed that BIOS functions may change registers if it is not explicitly stated not to do so. At least this is the safest approach and it has not caused too much extra work for me to save essential register values before the call.
User avatar
Combuster
Member
Member
Posts: 9301
Joined: Wed Oct 18, 2006 3:45 am
Libera.chat IRC: [com]buster
Location: On the balcony, where I can actually keep 1½m distance
Contact:

Re: Bootsector bug

Post by Combuster »

suslik wrote:To Combuster: When switching to Unreal mode I load to ES selector of data segment descriptor with base=0, limit=4GB:
Read again. Limit is 4G indeed, but offset is the same garbage the BIOS left you with (hint).
"Certainly avoid yourself. He is a newbie and might not realize it. You'll hate his code deeply a few years down the road." - Sortie
[ My OS ] [ VDisk/SFS ]
Post Reply