fixing up a bunch of files including the bootloader and kernel malloc kmalloc

This commit is contained in:
Gregory Kenneth Bowne 2024-06-12 18:10:23 -07:00
parent 79edf9eb6e
commit 3554f240a8
18 changed files with 968 additions and 461 deletions

BIN
.vscode/browse.vc.db vendored

Binary file not shown.

Binary file not shown.

View File

@ -1,165 +1,249 @@
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; [bits 16]
; Stage 1 bootloader for ClassicOS ; [org 0x7c00]
; -------------------------------- ;
; Determines if it was loaded from ;
; a floppy disk or an hard disk ;
; drive, and then loads stage 2 ;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;;;;;;;;;;;;;;;;;;;;;;;
; Assembler directives ;
;;;;;;;;;;;;;;;;;;;;;;;;
; tells the assembler that the program will be loaded at 0x7C00
; this is done by the BIOS
org 0x7C00
; we are targeting (x86) 16-bit real mode
bits 16
;;;;;;;;;;;;;;;;;
; Jump to start ;
;;;;;;;;;;;;;;;;;
jmp start
;;;;;;;;
; Data ;
;;;;;;;;
; fdd geometry & options
fddsamt db 1 ; how many sectors to load
fddretr db 5 ; max retries for fdd operations
fddcretr db 0 ; current retries left
; misc strings
welcome1 db "Welcome to the ClassicOS Stage 1 bootloader.", 13, 10, 0
disktype db "Drive type: ", 0
diskfdd db "FDD", 13, 10, 0
diskhdd db "HDD", 13, 10, 0
loaded db "Data loaded!", 13, 10, 0
; errors
fdderes db "FDD reset failed.", 13, 10, 0
fddeload db "FDD read failed.", 13, 10, 0
; storage
disknum db 0
;;;;;;;;;;;
; Program ;
;;;;;;;;;;;
start: start:
xor ax, ax ; set up segment registers to segment 0 since ;Set up segments correctly
mov ds, ax ; our addresses are already relative to 0x7C00 xor ax, ax
mov es, ax mov ds, ax
mov es, ax
mov fs, ax
mov gs, ax
mov [disknum], dl ; save disk number to memory ;Set up stack
mov ss, ax
mov bp, 0x7c00
mov sp, bp
mov ah, 0x01 ; set cursor shape ;Save boot device number
mov cx, 0x0100 ; hide cursor by setting ch = 1 and cl = 0x00 mov [bootdev], dl
int 0x10 ; video interrupt
mov ah, 0x08 ; read page number into bh ;Enable A20 Gate
int 0x10 EnableA20Gate:
call TestA20
cmp ax, 1
je A20Enabled
mov si, welcome1 ; print welcome tryUsingBIOS:
call printstr mov ax, 0x2401
int 0x15
call TestA20
cmp ax, 1
je A20Enabled
mov si, disktype ; print first part of disk type tryUsingKeyboardController:
call printstr cli
call WaitCommand
mov al, 0xAD ;Disable the keyboard
out 0x64, al
mov dl, [disknum] ; restore disk number - should not be call WaitCommand
; strictly necessary but you never know mov al, 0xD0 ;Read from input
and dl, 0x80 ; sets zf if disk is floppy out 0x64, al
jz fddload
hddload: call WaitData
mov si, diskhdd ; print disk type in al, 0x60 ;Read input from keyboard
call printstr push ax ;Save it
jmp load_onto_reset
fddload: call WaitCommand
mov si, diskfdd ; print disk type mov al, 0xD1 ;Write to output
call printstr out 0x64, al
load_onto_reset: call WaitCommand
mov ah, [fddretr] ; load max retries in memory pop ax ;Write to input back with bit #2 set
mov [fddcretr], ah or al, 2
load_reset: out 0x60, al
mov si, fdderes ; load error message pointer
dec byte [fddcretr] ; decrement the retries counter
jz load_err ; if it is 0, we stop trying
mov ah, 0x00 ; otherwise, reset function (int 0x13) call WaitCommand
int 0x13 mov al, 0xAE ;Enable Keyboard
jc load_reset ; if jc (error), we try again out 0x64, al
load_onto_load: call WaitCommand
mov ah, [fddretr] ; reset retries counter sti
mov [fddcretr], ah jmp A20KeyboardCheck
mov ax, 0x8000 ; need to stay within real mode limits
mov es, ax
load_load: ; loads 512*fddsamt bytes from sector 2 on.
mov si, fddeload
dec byte [fddcretr]
jz load_err
mov dh, 0 ; head 0 WaitCommand:
mov ch, 0 ; cyl/track 0 in al, 0x64
mov cl, 2 ; start sector test al, 2
mov bx, 0x8000 ; memory location jnz WaitCommand
mov al, [fddsamt] ; how many sectors to read ret
mov ah, 0x02 ; read function (int 0x13)
int 0x13
jc load_load ; if jc (error), we try again
cmp al, [fddsamt] ; also if al is not 1, we have a problem
jnz load_load
load_done: WaitData:
mov si, loaded ; we have successfully loaded the data in al, 0x64
call printstr test al, 1
jmp 0x8000:0x0000 ; this will be jmp 0x1000:0x0000 jz WaitData
ret
load_err: A20KeyboardCheck:
call printstr ; print call TestA20
jmp halt ; and die cmp ax, 1
je A20Enabled
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; UseFastA20Method:
; printstr routine, prints the string pointed by si using int 0x10 ; in al, 0x92
; sets the direction flag to 0 ; or al, 2
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; out 0x92, al
printstr: call TestA20
cld ; clear df flag - lodsb increments si cmp ax, 1
printstr_loop: je A20Enabled
lodsb ; load next character into al, increment si
or al, al ; sets zf if al is 0x00
jz printstr_end
mov ah, 0x0E ; teletype output (int 0x10)
int 0x10 ; print character
jmp printstr_loop
printstr_end:
ret ; return to caller address
;Else bail out, A20 cannot be enabled, maybe :)
A20Error:
mov si, A20_error_msg
call print
xor ax, ax
int 16h
xor ax, ax
int 19h
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; jmp $
; halt routine - infinite loop ; ;If we ever get here, A20 is enabled!
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; A20Enabled:
halt: LoadSecondStage:
cli push es
jmp halt mov ax, 0x7e0
mov es, ax
;;;;;;;;;;; stc
; Padding ; mov dh, 0
;;;;;;;;;;; mov ah, 0x02
; $ is the address of the current line, $$ is the base address for mov al, 2 ;load 2 sectors
; this program. mov ch, 0
; the expression is expanded to 510 - ($ - 0x7C00), or mov cl, 2
; 510 + 0x7C00 - $, which is, in other words, the number of bytes
; before the address 510 + 0x7C00 (= 0x7DFD), where the 0xAA55
; signature shall be put.
times 510 - ($ - $$) db 0x00
;;;;;;;;;;;;;;;;;; mov dl, [bootdev]
; BIOS signature ;
;;;;;;;;;;;;;;;;;; xor bx, bx ; [es:bx] = 0x07e0:0x0000
dw 0xAA55 int 13h
jnc load_success
disk_error:
mov si, disk_read_error_msg
call print
xor ax, ax
int 16h
xor ax, ax
int 19h
jmp $
load_success:
pop es
mov dl, [bootdev]
jmp 0x07e0:0x0000
jmp $
;Print string routine
print:
pusha
.loop:
lodsb
cmp al, 0
je .done
mov ah, 0x0e
int 10h
jmp .loop
.done:
popa
ret
;****************************
;Function to check if A20 Gate is enabled
;IN = nothing
;OUT : AX = status; 0 = Disabled, 1 = Enabled
TestA20:
cli
push es
push di
push ds
push si
push bx
push dx
xor dx, dx
xor bx, bx
mov es, bx
mov di, 0x0500
mov bx, 0xffff
mov ds, bx
mov si, 0x0510
mov al, byte [es:di]
push ax
mov al, byte [ds:si]
push ax
mov [es:di], byte 0x00
mov [ds:si], byte 0xff
mov bl, byte [es:di]
cmp bl, 0xff
je A20Exit
mov dx, 0x0001 ;A20 Enabled
A20Exit:
pop ax
mov [ds:si], al
pop ax
mov [es:di], al
mov ax, dx
pop dx
pop bx
pop si
pop ds
pop di
pop es
sti
ret
;;;;;;End of function;;;;;;;;;;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
disk_read_error_msg db 'Error Reading disk. Press any key to reboot. Code : 0x01', 0
A20_error_msg db 'An Internal error occured. Press any key to reboot. Code: 0x02', 0
bootdev db 0
times 442 - ($-$$) db 0
dd 0x07112026 ;Boot signature: Unique for each boot disk this OS is installed on ;6:20 PM
;Written on 7th November, 2020 6:20 pm
;Partition tables
; #1
db 0x0
db 0
db 0
db 0
db 0x00 ;Reserved
db 0
db 0
db 0
dd 0x0
dd 20480
; #2
db 0x80
db 0
db 0
db 0
db 07h ;FAT 32 fs
db 0
db 0
db 0
dd 20480
dd 8388608
; #3
times 16 db 0
; #4
times 16 db 0
dw 0xaa55

Binary file not shown.

View File

@ -1,133 +1,473 @@
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; [bits 16]
; Stage 2 bootloader for ClassicOS ; [org 0x7e00]
; -------------------------------- ;
; Loads the kernel, sets up tables, ; start:
; and transitions to protected mode ; mov [bootdev], dl
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
GetVesaControllerInfo:
;;;;;;;;;;;;;;;;;;;;;;;; ;Preset 1st 4 bytes of block with
; Assembler directives ; ; 'VBE2' to get VBE2 information
;;;;;;;;;;;;;;;;;;;;;;;;
mov di, VESAControllerInfo
; tells the assembler that the program will be loaded at 0x8000 mov byte [di], 'V'
; this is done by the first stage bootloader mov byte [di+1], 'B'
org 0x8000 mov byte [di+2], 'E'
mov byte [di+3], '2'
; we are targeting (x86) 16-bit real mode
bits 16 ;Function 00h: get VESA controller information
;;;;;;;;;;;;;;;;; mov ax, 0x4f00
; Jump to start ; int 10h
;;;;;;;;;;;;;;;;;
jmp start ;Get pointer to list of supported modes
mov ax, word [VESAControllerInfo+14]
;;;;;;;;
; Data ; push ax
;;;;;;;; shr ax, 4 ;Grab segment of pointer
; kernel file name mov bx, ax ;and save it
kername db "KERNEL.BIN", 0
pop ax
;;;;;;;;;;; and ax, 0x000f
; Program ;
;;;;;;;;;;; mov dx, word [VESAControllerInfo+16] ;pointer's offset
add dx, ax
start:
xor ax, ax ; set up segment registers to segment 0 since push es ;Save 'es' on stack
mov ds, ax ; our addresses are already relative to 0x8000 mov es, bx ;Segment
mov es, ax mov di, dx ;Offset
; mov si, VESAControllerInfo ;Print VESA
mov si, kername ; print kernel file name ; call print
call printstr
save_available_video_modes:
; Load the kernel into memory mov bx, VbeModeList
%include "kernel_loader.asm"
.save_modes_loop: ;Save all available modes
; Set up IVT (GTD and IDT not used in 16 bit real mode) mov ax, word [es:di]
; Define interrupt handlers (replace with your actual handler code)
div_by_zero_handler: cmp ax, 0xffff ;End of list?
cli je finished_mode_save
hlt
mov [bx], ax ;Save mode number
timer_handler:
; Your timer interrupt handler code add bx, 2
hlt add di, 2
ret jmp .save_modes_loop
; IVT entries (offset 0 for all handlers since segment 0) finished_mode_save:
times 0x100 dw 0x0000 ; Initialize unused entries mov [bx], ax
dw offset div_by_zero_handler ; Interrupt 0 (Division by Zero) pop es
times 0x7 dw 0x0000 ; Skip unused entries jmp short do_e820
dw offset timer_handler ; Interrupt 0x8 (Timer)
mmap_ent equ mem_map_entries_count ; the number of entries will be stored at mem_map_entries_count
; Switch to protected mode
; Enable Protected Mode do_e820:
switch_to_protected_mode: pusha
cli ; Disable interrupts push es
mov eax, cr0 ; Get current CR0 value push bp
or eax, 0x01 ; Set PE bit (Protected Mode Enable)
mov cr0, eax ; Write modified CR0 value back mov ax, 0x3000
mov es, ax
; Set up stack and start executing kernel's code mov di, 0
; Define GDT structure (replace with your actual GDT definition) xor ebx, ebx ; ebx must be 0 to start
gdt_start: ; Beginning of GDT xor bp, bp ; keep an entry count in bp
times 5 dd 0 ; Null descriptor entries (optional) mov edx, 0x0534D4150 ; Place "SMAP" into edx
gdt_code: ; Code segment descriptor mov eax, 0x0000e820
dw 0xffff ; Segment size (limit) mov [es:di + 20], dword 1 ; force a valid ACPI 3.X entry
dw 0x0000 ; Segment base address (low) mov ecx, 24 ; ask for 24 bytes
db 0x0 ; Segment base address (high) int 0x15
db 10011010b ; Access rights (present, readable, conforming, executable) jc short .failed ; carry set on first call means "unsupported function"
db 11001111b ; Access rights (long mode, 4-granularity, size) mov edx, 0x0534D4150 ; Some BIOSes apparently trash this register?
gdt_end: ; End of GDT cmp eax, edx ; on success, eax must have been reset to "SMAP"
gdt_descriptor: jne short .failed
equ gdt_end - gdt_start ; Size of GDT test ebx, ebx ; ebx = 0 implies list is only 1 entry long (worthless)
dw gdt_descriptor ; Offset of GDT je short .failed
dd gdt_start ; Base address of GDT jmp short .jmpin
; Load the GDT .e820lp:
lgdt [gdt_descriptor] ; Load GDT descriptor into GDTR mov eax, 0xe820 ; eax, ecx get trashed on every int 0x15 call
mov [es:di + 20], dword 1 ; force a valid ACPI 3.X entry
; Set up Stack (replace with your actual stack segment and address) mov ecx, 24 ; ask for 24 bytes again
mov ss, data_segment ; Set stack segment selector int 0x15
mov esp, 0x100000 ; Set stack pointer (top of stack) jc short .e820f ; carry set means "end of list already reached"
mov edx, 0x0534D4150 ; repair potentially trashed register
; Start Kernel Execution
jmp farptr kernel_entry ; Jump to kernel entry point (replace with actual address) .jmpin:
jcxz .skipent ; skip any 0 length entries
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; cmp cl, 20 ; got a 24 byte ACPI 3.X response?
; printstr routine, prints the string pointed by si using int 0x10 ; jbe short .notext
; sets the direction flag to 0 ; test byte [es:di + 20], 1 ; if so: is the "ignore this data" bit clear?
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; je short .skipent
printstr:
cld ; clear df flag - lodsb increments si .notext:
printstr_loop: mov ecx, [es:di + 8] ; get lower uint32_t of memory region length
lodsb ; load next character into al, increment si or ecx, [es:di + 12] ; "or" it with upper uint32_t to test for zero
or al, al ; sets zf if al is 0x00 jz .skipent ; if length uint64_t is 0, skip entry
jz printstr_end inc bp ; got a good entry: ++count, move to next storage spot
mov ah, 0x0E ; teletype output (int 0x10) add di, 24
int 0x10 ; print character
jmp printstr_loop .skipent:
printstr_end: test ebx, ebx ; if ebx resets to 0, list is complete
ret ; return to caller address jne short .e820lp
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; .e820f:
; halt routine - infinite loop ; mov [mmap_ent], bp ; store the entry count
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; clc ; there is "jc" on end of list to this point, so the carry must be cleared
halt:
cli mov dword [mem_map], 0x30000 ; the memory map is stored at this address
jmp halt
pop bp
;;;;;;;;;;; pop es
; Padding ; popa
;;;;;;;;;;; jmp short load_kernel
; $ is the address of the current line, $$ is the base address for
; this program. .failed:
; the expression is expanded to 510 - ($ - 0x8000), or mov si, memory_error
; 510 + 0x8000 - $, which is, in other words, the number of bytes call print
; before the address 510 + 0x8000 (= 0x80FD), where the 0xAA55 jmp $
; signature shall be put.
times 510 - ($ - $$) db 0x00 load_kernel:
;;;;;;;;;;;;;;;;;; mov ah, 8
; BIOS signature ; mov dl, [bootdev]
;;;;;;;;;;;;;;;;;; int 13h ;Get drive params
dw 0xAA55
jc disk_error
and cx, 111111b
mov [sectorsPerTrack], cx
mov [numHeads], dh
inc word [numHeads]
push es
mov ax, 0x900
mov es, ax
stc
mov dh, 0
mov ah, 0x02
mov al, 120 ;load 120 sectors
mov ch, 0
mov cl, 4 ;Kernel is at the fourth sector of the disk
mov dl, [bootdev]
xor bx, bx ; [es:bx] = 0x0900:0x0000
int 13h
jc disk_error
mov ax, 0x1800
mov es, ax
stc
mov ax, 123
call getchs
mov dh, [head]
mov ah, 0x02
mov al, 120 ;load another 120 sectors making a total of 240 sectors
mov ch, [cyl]
mov cl, [sect]
mov dl, [bootdev]
xor bx, bx ;[es:bx] = 0x1800:0x0000
int 13h
jnc switch_video_mode
disk_error:
mov si, disk_read_error_msg
call print
xor ax, ax
int 16h
xor ax, ax
int 19h
switch_video_mode:
pop es
mov di, VbeModeList
.loop:
mov ax, word [es:di]
cmp ax, 0xFFFF
je next_mode
mov cx, ax ;Save mode number in cx
push di
mov di, VbeModeInfo
mov ax, 4f01h
int 10h
;This searches for 32bpp 1024*768 <Default OS Mode>
cmp byte [di+25], 0x20 ;Bits Per Pixel
jne .continue
cmp WORD [di+18], 1024
jne .continue
cmp WORD [di+20], 768
je found_mode
.continue:
pop di
add di, 2
jmp .loop
found_mode:
mov [CurrentMode], cx
mov di, VbeModeInfo
mov ax, 0x4f01
int 10h
mov bx, cx
mov ax, 0x4f02 ;Set vbe mode
; int 10h
jmp EnablePaging
jmp $
next_mode:
mov di, VbeModeList
.loop:
mov ax, word [es:di]
cmp ax, 0xFFFF
je no_mode_found
mov cx, ax ;Save mode number in cx
push di
mov di, VbeModeInfo
mov ax, 4f01h
int 10h
;This searches for 32bpp 1280 * 1024
cmp byte [di+25], 0x20 ;Bits Per Pixel
jne .continue
cmp WORD [di+18], 1280
jne .continue
cmp WORD [di+20], 1024
je found_mode
.continue:
pop di
add di, 2
jmp .loop
;For now, only two modes are supported in this OS
no_mode_found:
mov si, no_mode_msg
call print
jmp $
;Print string routine
print:
pusha
.loop:
lodsb
cmp al, 0
je .done
mov ah, 0x0e
int 10h
jmp .loop
.done:
popa
ret
;GETCHS Function
;put lba value to convert in ax
;returns cyl, head, sect
cyl db 0
head db 0
sect db 0
sectorsPerTrack dw 0
numHeads dw 0
getchs:
xor dx,dx
mov bx,[sectorsPerTrack]
div bx
inc dx
mov byte [sect],dl
xor dx,dx
mov bx,[numHeads]
div bx
mov byte [cyl],al
mov byte [head],dl
ret
jmp $
EnablePaging:
.fill_page_directory:
push es
mov ax, 0x2900
mov es, ax
mov cx, 1024
mov di, 0
.paging_loop0: ;Fill the page directory with zeros
mov dword [es:di], 0x00000002
add di, 4
loop .paging_loop0
;Fill the first two page table to map the first 8MB of memory.
; The remaining tables will be filled once the switch to protected mode is made and more memory
; can be accessed.
.fill_first_page_table:
mov ax, 0x2A00
mov es, ax
mov cx, 1024
mov di, 0x0000
mov esi, 0x00000003
.paging_loop1:
mov dword [es:di], esi
add di, 4
add esi, 0x1000
loop .paging_loop1
.fill_second_page_table:
mov ax, 0x2B00
mov es, ax
mov cx, 1024
mov di, 0
mov esi, 0x00400003
.paging_loop2:
mov dword [es:di], esi
add di, 4
add esi, 0x1000
loop .paging_loop2
loadPageTables: ;Map the first 8mb
mov ax, 0x2900
mov es, ax
mov di, 0x0000
mov dword [es:di], 0x2A003 ;Page directory entry 0 (0-3.99MB)
add di, 4
mov dword [es:di], 0x2B003 ;Page directory entry 1 (4-7.99MB)
loadGDT:
lgdt [gdt_descriptor] ;Load the Global Descriptor Table
loadPageDirectory:
pop es
mov dword [page_directory], 0x29000 ;Save the linear address of the page directory
mov eax, 0x29000 ;Load the page directory address to cr3
mov cr3, eax
switch_to_pmode:
cli
mov eax, cr0
or eax, 0x80000001 ;Turn on paging (bit 31) and protected mode enable (bit 0)
mov cr0, eax
jmp CODE_SEG:BEGIN_PM
;Data
;THE GLOBAL DESCRIPTOR TABLE
gdt_start:
dd 0x0
dd 0x0
gdt_code:
dw 0xffff
dw 0x0
db 0x0
db 0x9a
db 11001111b
db 0x0
gdt_data:
dw 0xffff
dw 0x0
db 0x0
db 0x92
db 11001111b
db 0x0
gdt_end:
gdt_descriptor:
dw gdt_end - gdt_start - 1
dd gdt_start
CODE_SEG equ gdt_code - gdt_start
DATA_SEG equ gdt_data - gdt_start
disk_read_error_msg: db "Error Loading OS Kernel. Press any key to reboot! Code: 0x01", 0
memory_error db "Memory test error! Reboot the PC to try again. Code: 0x03" ,0
no_mode_msg db 'No supported video mode found. Code: 0x04' , 0
bootdev db 0
[BITS 32]
BEGIN_PM:
;Set up segments
mov ax, DATA_SEG
mov ds, ax
mov es, ax
mov fs, ax
mov gs, ax
mov ss, ax ;Set up stack segment
mov ebp, 0x1F0000 ;and pointer
mov esp, ebp
mov ecx, 512*240 ;We have 240 sectors loaded
mov esi, 0x9000 ;at address 0x9000
mov edi, 0x100000 ;we must copy them to 0x100000
rep movsb ;perform copy from EDI to ESI
; Map the whole 4Gb 0f memory
fillPageTables:
mov esi, 0x200000
mov ecx, 1048576 ;1024 page directory entries * 1024 entries per page table
mov eax, 0x00000003
.paging_loop3:
mov dword [esi], eax
add esi, 4
add eax, 0x1000
loop .paging_loop3
.loadAllPageTables:
mov ecx, 1024
mov eax, 0x200003
mov esi, 0x29000
.paging_loop4:
mov dword [esi] ,eax
add eax, 0x1000
add esi, 4
loop .paging_loop4
;;;;;;;;;;;;;;;;;;;;;;;;;;;;
mov eax, kernel_info_block
call 0x100000 ;Jump to kernel's entry point
_stop:
hlt
jmp _stop
times 1024 - ($-$$) db 0
section .bss
kernel_info_block:
VESAControllerInfo: resb 512 ;0x8200
VbeModeList: resw 128 ;0x8400
CurrentMode: resw 1 ;0x8500
VbeModeInfo: resb 256 ;0x8502
mem_map_entries_count: resd 1 ;0x8602
mem_map: resd 1 ;0x8606
page_directory: resd 1; 0x860A

BIN
src/boot/boot2.bin Normal file

Binary file not shown.

View File

@ -1,23 +0,0 @@
; Define constants (adjust as needed)
boot_drive equ 0x00 ; Drive to load kernel from (usually 0 for primary)
kernel_sector equ 1 ; Sector containing the kernel (adjust for your kernel's location)
kernel_segments equ 4 ; Number of sectors to load (adjust for your kernel size)
kernel_load_address equ 0x1000 ; Memory address to load the kernel
void int_13h(unsigned int ah, unsigned int al, unsigned int dx, unsigned int ch, unsigned int cl, unsigned int bx);
void error_handler(const char *message)
; Main kernel loading code
mov bx, kernel_load_address ; Set load address
; Loop to load kernel sectors
mov cx, 0 ; Initialize counter
loop_load:
int_13h(0x02, kernel_segments, boot_drive * 256 + kernel_sector, ch, cl, bx) ; Read sectors
add bx, 512 * kernel_segments ; Update load address
inc cx ; Increment counter
cmp cx, kernel_segments ; Check if all sectors loaded
jne loop_load ; Jump back if not finished
; Success - kernel is now loaded into memory
ret ; Return to the main bootloader code

View File

@ -1,31 +1,25 @@
ENTRY(start) ENTRY(start)
SECTIONS { SECTIONS
. = 0x7c00; {
.text :
.text : { {
*(.text) *(.text)
} }
.data : { .data :
{
*(.data) *(.data)
} }
.bss : { .bss :
{
*(.bss) *(.bss)
} }
/* Define the bootloader signature at the end of the bootloader */ .kernel :
bootloader_signature : { {
*(.bootloader_signature) /* Kernel code */
} . = 0x9000; /* Start of kernel code section */
*(.kernel)
/* Define the bootloader magic number at the end of the bootloader */
bootloader_magic : {
*(.bootloader_magic)
}
/* Define the bootloader padding to fill up the remaining space */
bootloader_padding : {
*(.bootloader_padding)
} }
} }

View File

@ -3,16 +3,30 @@
global cpuid global cpuid
cpuid: cpuid:
; Input parameter in EAX register ; Save registers
mov eax, %edi push ebp
mov ebp, esp
push ebx
push edi
push esi
; Call CPUID instruction (clobbers EAX, EBX, ECX, EDX) ; Input parameter in EAX register
cpuid mov eax, [ebp + 8] ; Assuming the input is passed on the stack
; Return values in output registers ; Call CPUID instruction (clobbers EAX, EBX, ECX, EDX)
mov %esi, [esp + 4] ; eax (output) cpuid
mov %edx, [esp + 8] ; ebx (output)
mov %ecx, [esp + 12] ; ecx (output)
mov %edi, [esp + 16] ; edx (output)
ret ; Move output values to the appropriate registers
mov esi, eax ; Output EAX
mov edi, ebx ; Output EBX
mov ecx, ecx ; Output ECX
mov edx, edx ; Output EDX
; Restore registers and clean up the stack
pop esi
pop edi
pop ebx
mov esp, ebp
pop ebp
ret

View File

@ -1,118 +1,137 @@
#include "eisa.h" #include "eisa.h"
#include <stdbool.h> #include <stdbool.h>
#include <stddef.h> #include <stddef.h>
#include <stdint.h> #include <stdint.h>
#include <stdio.h> #include <stdio.h>
#define MY_DEVICE_VENDOR_ID 0x1234 #define MY_DEVICE_VENDOR_ID 0x1234
#define MY_DEVICE_DEVICE_ID 0x5678 #define MY_DEVICE_DEVICE_ID 0x5678
#define MY_DEVICE_CLASS_CODE 0x90AB #define MY_DEVICE_CLASS_CODE 0x90AB
// EISA bus controller base address // EISA bus controller base address
#define EISA_BASE_ADDRESS 0x0000 #define EISA_BASE_ADDRESS 0x0000
// EISA bus controller data port // EISA bus controller data port
#define EISA_DATA_PORT 0x00 #define EISA_DATA_PORT 0x00
// EISA bus controller command port // EISA bus controller command port
#define EISA_COMMAND_PORT 0x01 #define EISA_COMMAND_PORT 0x01
// Initialize the EISA bus // Initialize the EISA bus
void eisa_init() void eisa_init()
{ {
// Add any necessary initialization code here // Add any necessary initialization code here
} }
// Detect and configure EISA devices // Detect and configure EISA devices
void eisa_detect_devices() void eisa_detect_devices()
{ {
uint32_t bus, slot, func; uint32_t bus, slot, func;
uint16_t vendor_id, device_id, class_code; uint16_t vendor_id, device_id, class_code;
for (bus = 0; bus < 256; bus++) for (bus = 0; bus < 256; bus++)
{ {
for (slot = 0; slot < 32; slot++) for (slot = 0; slot < 32; slot++)
{ {
for (func = 0; func < 8; func++) for (func = 0; func < 8; func++)
{ {
uint32_t address = (bus << 16) | (slot << 11) | (func << 8); uint32_t address = (bus << 16) | (slot << 11) | (func << 8);
uint32_t id = eisa_read_config_dword(address, 0); uint32_t id = eisa_read_config_dword(address, 0);
vendor_id = id & 0xFFFF; vendor_id = id & 0xFFFF;
device_id = (id >> 16) & 0xFFFF; device_id = (id >> 16) & 0xFFFF;
class_code = eisa_read_config_word(address, 10); class_code = eisa_read_config_word(address, 10);
if (vendor_id != 0xFFFF) if (vendor_id != 0xFFFF)
{ {
// Device detected, do something with it // Device detected, do something with it
if (vendor_id == MY_DEVICE_VENDOR_ID && if (vendor_id == MY_DEVICE_VENDOR_ID &&
device_id == MY_DEVICE_DEVICE_ID && device_id == MY_DEVICE_DEVICE_ID &&
class_code == MY_DEVICE_CLASS_CODE) class_code == MY_DEVICE_CLASS_CODE)
{ {
// This is my device, configure it // This is my device, configure it
uint32_t config1 = eisa_read_config_dword(address, 4); uint32_t config1 = eisa_read_config_dword(address, 4);
uint32_t config2 = eisa_read_config_dword(address, 8); uint32_t config2 = eisa_read_config_dword(address, 8);
//printf("Config1: %u\n", config1);
//printf("Config2: %u\n", config2); //printf("Config1: %u\n", config1);
// Do something with the configuration data //printf("Config2: %u\n", config2);
} // Do something with the configuration data
}
} // Check for specific bits in config1
} if (config1 & 0x00000001) {
} // Enable feature 1 based on bit 0 of config1
} eisa_write(0xspecific_port_1, 0xvalue_to_enable_feature_1);
}
// Read a double word (32 bits) from an EISA device's configuration space
uint32_t eisa_read_config_dword(uint32_t address, uint8_t offset) if (config1 & 0x00000010) {
{ // Set DMA channel based on bits 4-5 of config1
// Set the EISA bus controller base address uint8_t dma_channel = (config1 >> 4) & 0x03;
eisa_write(EISA_BASE_ADDRESS, address); eisa_write(0xspecific_port_2, dma_channel);
}
// Set the EISA bus controller command port to read configuration data
eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03)); // Check for specific bits in config2
if (config2 & 0x00000001) {
// Read the double word from the EISA bus controller data port // Configure interrupt line based on bit 0 of config2
uint32_t value = 0; eisa_write(0xspecific_port_3, 0xinterrupt_line_number);
for (int i = 0; i < 4; i++) }
{ }
value |= (eisa_read(EISA_DATA_PORT) << (i * 8)); }
} }
}
return value; }
} }
// Read a word (16 bits) from an EISA device's configuration space // Read a double word (32 bits) from an EISA device's configuration space
uint16_t eisa_read_config_word(uint32_t address, uint8_t offset) uint32_t eisa_read_config_dword(uint32_t address, uint8_t offset)
{ {
// Set the EISA bus controller base address // Set the EISA bus controller base address
eisa_write(EISA_BASE_ADDRESS, address); eisa_write(EISA_BASE_ADDRESS, address);
// Set the EISA bus controller command port to read configuration data // Set the EISA bus controller command port to read configuration data
eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03)); eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03));
// Read the word from the EISA bus controller data port // Read the double word from the EISA bus controller data port
uint16_t value = 0; uint32_t value = 0;
for (int i = 0; i < 2; i++) for (int i = 0; i < 4; i++)
{ {
value |= (eisa_read(EISA_DATA_PORT) << (i * 8)); value |= (eisa_read(EISA_DATA_PORT) << (i * 8));
} }
return value; return value;
} }
// Read from an EISA device // Read a word (16 bits) from an EISA device's configuration space
uint8_t eisa_read(uint16_t port) uint16_t eisa_read_config_word(uint32_t address, uint8_t offset)
{ {
uint8_t value; // Set the EISA bus controller base address
eisa_write(EISA_BASE_ADDRESS, address);
// Read from the specified port
__asm__ volatile("inb %1, %0" : "=a"(value) : "dN"(port)); // Set the EISA bus controller command port to read configuration data
eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03));
return value;
} // Read the word from the EISA bus controller data port
uint16_t value = 0;
// Write to an EISA device for (int i = 0; i < 2; i++)
void eisa_write(uint16_t port, uint8_t value) {
{ value |= (eisa_read(EISA_DATA_PORT) << (i * 8));
// Write the specified value to the specified port }
__asm__ volatile("outb %0, %1" : : "a"(value), "dN"(port));
} return value;
}
// Read from an EISA device
uint8_t eisa_read(uint16_t port)
{
uint8_t value;
// Read from the specified port
__asm__ volatile("inb %1, %0" : "=a"(value) : "dN"(port));
return value;
}
// Write to an EISA device
void eisa_write(uint16_t port, uint8_t value)
{
// Write the specified value to the specified port
__asm__ volatile("outb %0, %1" : : "a"(value), "dN"(port));
}

View File

@ -1,16 +1,27 @@
#include "fat16.h" #include "fat16.h"
#include <stdint.h> #include <stdint.h>
#include "fat16_io.h" #include "fat16_io.h"
#include "src/kernel/arch/x86/disk/ata.h"
// Implementation of read_sector and write_sector functions (replace with actual disk I/O) // Implementation of read_sector and write_sector functions (replace with actual disk I/O)
int read_sector(uint32_t sector_number, void *buffer) int read_sector(uint32_t sector_number, void *buffer)
{ {
// ... (Code to read a sector from disk) ... // ... (Code to read a sector from disk) ...
// Calculate physical disk location based on sector number
uint32_t head, sector, cylinder;
translate_logical_to_physical(sector_number, &head, &sector, &cylinder); // Replace with your driver's translation function
// Issue read command to disk controller
if (disk_read_sector(head, sector, cylinder, buffer) != 0) {
// Error handling: This could involve setting an error flag or returning a specific error code
return -1; // Example error code
}
return 0; // Success
} }
int write_sector(uint32_t sector_number, void *buffer) int write_sector(uint32_t sector_number, void *buffer)
{ {
return read_sector_from_disk(sector_number, buffer); return read_sector(sector_number, buffer); // Use the existing read_sector function
} }
// Function to parse the boot sector (replace with actual parsing logic) // Function to parse the boot sector (replace with actual parsing logic)

View File

@ -2,6 +2,9 @@
#define FAT16_H #define FAT16_H
#include <stdint.h> #include <stdint.h>
#include "../../ata.h"
// Define constants for sector size, cluster size, etc. (replace with actual values) // Define constants for sector size, cluster size, etc. (replace with actual values)
#define SECTOR_SIZE 512 #define SECTOR_SIZE 512
#define BYTES_PER_CLUSTER 4096 // Example: 8 sectors per cluster #define BYTES_PER_CLUSTER 4096 // Example: 8 sectors per cluster

View File

@ -1,5 +1,7 @@
#include "fat16_io.h" #include "fat16_io.h"
#include <stdint.h> #include <stdint.h>
#include "src/kernel/arch/x86/disk/ata.h"
#include "fat16.h"
// I/O port addresses for IDE controller (replace with actual values if needed) // I/O port addresses for IDE controller (replace with actual values if needed)
#define PRIMARY_DATA_REGISTER 0x1F0 #define PRIMARY_DATA_REGISTER 0x1F0
#define PRIMARY_ERROR_REGISTER 0x1F1 #define PRIMARY_ERROR_REGISTER 0x1F1

View File

@ -2,6 +2,8 @@
#define FAT16_IO_H #define FAT16_IO_H
#include <stdint.h> #include <stdint.h>
#include "fat16.h"
#include "src/kernel/arch/x86/disk/ata.h"
// I/O port addresses for IDE controller (replace with actual values if needed) // I/O port addresses for IDE controller (replace with actual values if needed)
#define PRIMARY_DATA_REGISTER 0x1F0 #define PRIMARY_DATA_REGISTER 0x1F0

View File

@ -0,0 +1,32 @@
#ifndef ATA_H
#define ATA_H
#include "../include/types.h"
// I/O port addresses for IDE controllers (replace with actual values if needed)
#define PRIMARY_DATA_REGISTER 0x1F0
#define PRIMARY_ERROR_REGISTER 0x1F1
#define PRIMARY_COMMAND_REGISTER 0x1F2
#define PRIMARY_SELECT_REGISTER 0x1F6
#define SECONDARY_DATA_REGISTER 0x1F4
#define SECONDARY_ERROR_REGISTER 0x1F5
#define SECONDARY_COMMAND_REGISTER 0x1F6
#define SECONDARY_SELECT_REGISTER 0x1F7
// Define bit masks for IDE commands (replace with actual values if needed)
#define ATA_CMD_READ_SECTORS_WITHOUT_RETRIES 0x20
#define ATA_CMD_READ_SECTORS_WITH_RETRIES 0xC4
#define ATA_CMD_WRITE_SECTORS_WITHOUT_RETRIES 0x30
#define ATA_CMD_WRITE_SECTORS_WITH_RETRIES 0x34
// Define bit masks for IDE status register bits (replace with actual values if needed)
#define ATA_STATUS_BSY 0x02 // Busy bit
#define ATA_STATUS_DRQ 0x08 // Data Request bit
#define ATA_STATUS_ERR 0x01 // Error bit
// Function prototypes (replace with actual function implementations)
int read_sector(uint32_t sector_number, void *buffer, int drive); // Read a sector from disk (drive: 0 for primary, 1 for secondary)
int write_sector(uint32_t sector_number, void *buffer, int drive); // Write a sector to disk (drive: 0 for primary, 1 for secondary)
// Additional function prototypes specific to your IDE controller library can be added here
#endif

View File

@ -1,4 +1,8 @@
#include "kernel.h" #include "kernel.h"
#include "./arch/x86/gdt.h"
#include "../kernel/malloc/malloc.h"
#include "../kernel/malloc/kmalloc.h"
#include "./arch/x86/include/memory.h"
#include <stdbool.h> #include <stdbool.h>
#include <stddef.h> #include <stddef.h>
#include <stdint.h> #include <stdint.h>
@ -45,6 +49,13 @@ void init_devices() {
// Placeholder for actual implementation // Placeholder for actual implementation
} }
void early_init() {
// ... other early initialization tasks
init_kernel_heap((void*)KERNEL_HEAP_START, (void*)KERNEL_HEAP_END);
// Initialize GDT
gdt_init();
}
void kernel_main() { void kernel_main() {
clear_screen(); clear_screen();
print("Welcome to ClassicOS!"); print("Welcome to ClassicOS!");
@ -52,6 +63,16 @@ void kernel_main() {
// Initialize memory management // Initialize memory management
init_memory_management(); init_memory_management();
// Initialize user-space heap (example)
void* user_heap_start = /* address of user-space heap start */;
void* user_heap_end = /* address of user-space heap end */;
init_heap(user_heap_start, user_heap_end);
// Initialize kernel heap (example)
void* kernel_heap_start = /* address of kernel heap start */;
void* kernel_heap_end = /* address of kernel heap end */;
init_kernel_heap(kernel_heap_start, kernel_heap_end);
// Initialize devices // Initialize devices
init_devices(); init_devices();
@ -70,4 +91,3 @@ void kernel_main() {
handle_system_calls(); handle_system_calls();
} }
} }

View File

@ -1,7 +1,4 @@
#ifndef KERNEL_H #ifndef KERNEL_H
#define KERNEL_H #define KERNEL_H
// Function to print a null-terminated string to the screen
void print_string(const char* str);
#endif #endif

View File

@ -1,12 +1,24 @@
#ifndef KMALLOC_H_ // Corrected guard macro #ifndef KMALLOC_H
#define KMALLOC_H_ #define KMALLOC_H
#include <stddef.h> // For size_t #include <stdint.h>
#include <stddef.h>
void *kmalloc(size_t size); // Structure to represent a memory block in the kernel heap
void kfree(void *ptr); typedef struct {
void* base; // Starting address of the block
size_t size; // Size of the block in bytes
struct heap_block* next; // Pointer to the next block in the free list
} heap_block_t;
void mark_as_used_kernel(void *ptr, size_t size); // Function prototypes
void mark_as_free_kernel(void *ptr); void init_kernel_heap(void* start, void* end);
void init_user_heap(void* start, void* end);
void* kmalloc(size_t size);
void kfree(void* ptr);
#endif /* KMALLOC_H_ */ // Global variable to store the free list head
extern heap_block_t* kheap_free_list;
#endif
/* KMALLOC_H_ */