diff --git a/.vscode/browse.vc.db b/.vscode/browse.vc.db index d1f5cb5..d3ab55d 100644 Binary files a/.vscode/browse.vc.db and b/.vscode/browse.vc.db differ diff --git a/.vscode/browse.vc.db-shm b/.vscode/browse.vc.db-shm index abe0035..d187c5c 100644 Binary files a/.vscode/browse.vc.db-shm and b/.vscode/browse.vc.db-shm differ diff --git a/src/boot/boot.asm b/src/boot/boot.asm index 9bb09e7..41f43c6 100644 --- a/src/boot/boot.asm +++ b/src/boot/boot.asm @@ -1,165 +1,249 @@ -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -; Stage 1 bootloader for ClassicOS ; -; -------------------------------- ; -; 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 ; -;;;;;;;;;;; +[bits 16] +[org 0x7c00] start: - xor ax, ax ; set up segment registers to segment 0 since - mov ds, ax ; our addresses are already relative to 0x7C00 - mov es, ax + ;Set up segments correctly + xor ax, 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 - mov cx, 0x0100 ; hide cursor by setting ch = 1 and cl = 0x00 - int 0x10 ; video interrupt + ;Save boot device number + mov [bootdev], dl - mov ah, 0x08 ; read page number into bh - int 0x10 +;Enable A20 Gate +EnableA20Gate: + call TestA20 + cmp ax, 1 + je A20Enabled - mov si, welcome1 ; print welcome - call printstr +tryUsingBIOS: + mov ax, 0x2401 + int 0x15 + call TestA20 + cmp ax, 1 + je A20Enabled - mov si, disktype ; print first part of disk type - call printstr +tryUsingKeyboardController: + cli + call WaitCommand + mov al, 0xAD ;Disable the keyboard + out 0x64, al - mov dl, [disknum] ; restore disk number - should not be - ; strictly necessary but you never know - and dl, 0x80 ; sets zf if disk is floppy - jz fddload + call WaitCommand + mov al, 0xD0 ;Read from input + out 0x64, al -hddload: - mov si, diskhdd ; print disk type - call printstr - jmp load_onto_reset + call WaitData + in al, 0x60 ;Read input from keyboard + push ax ;Save it -fddload: - mov si, diskfdd ; print disk type - call printstr + call WaitCommand + mov al, 0xD1 ;Write to output + out 0x64, al -load_onto_reset: - mov ah, [fddretr] ; load max retries in memory - mov [fddcretr], ah -load_reset: - mov si, fdderes ; load error message pointer - dec byte [fddcretr] ; decrement the retries counter - jz load_err ; if it is 0, we stop trying + call WaitCommand + pop ax ;Write to input back with bit #2 set + or al, 2 + out 0x60, al - mov ah, 0x00 ; otherwise, reset function (int 0x13) - int 0x13 - jc load_reset ; if jc (error), we try again + call WaitCommand + mov al, 0xAE ;Enable Keyboard + out 0x64, al -load_onto_load: - mov ah, [fddretr] ; reset retries counter - mov [fddcretr], ah - 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 + call WaitCommand + sti + jmp A20KeyboardCheck - mov dh, 0 ; head 0 - mov ch, 0 ; cyl/track 0 - mov cl, 2 ; start sector - mov bx, 0x8000 ; memory location - mov al, [fddsamt] ; how many sectors to read - 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 +WaitCommand: + in al, 0x64 + test al, 2 + jnz WaitCommand + ret -load_done: - mov si, loaded ; we have successfully loaded the data - call printstr - jmp 0x8000:0x0000 ; this will be jmp 0x1000:0x0000 +WaitData: + in al, 0x64 + test al, 1 + jz WaitData + ret -load_err: - call printstr ; print - jmp halt ; and die +A20KeyboardCheck: + call TestA20 + cmp ax, 1 + je A20Enabled -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -; printstr routine, prints the string pointed by si using int 0x10 ; -; sets the direction flag to 0 ; -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -printstr: - cld ; clear df flag - lodsb increments si -printstr_loop: - 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 +UseFastA20Method: + in al, 0x92 + or al, 2 + out 0x92, al + call TestA20 + cmp ax, 1 + je A20Enabled +;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 -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -; halt routine - infinite loop ; -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -halt: - cli - jmp halt +jmp $ +;If we ever get here, A20 is enabled! +A20Enabled: +LoadSecondStage: + push es + mov ax, 0x7e0 + mov es, ax -;;;;;;;;;;; -; Padding ; -;;;;;;;;;;; -; $ is the address of the current line, $$ is the base address for -; this program. -; the expression is expanded to 510 - ($ - 0x7C00), or -; 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 + stc + mov dh, 0 + mov ah, 0x02 + mov al, 2 ;load 2 sectors + mov ch, 0 + mov cl, 2 -;;;;;;;;;;;;;;;;;; -; BIOS signature ; -;;;;;;;;;;;;;;;;;; -dw 0xAA55 \ No newline at end of file + mov dl, [bootdev] + + xor bx, bx ; [es:bx] = 0x07e0:0x0000 + 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 \ No newline at end of file diff --git a/src/boot/boot.bin b/src/boot/boot.bin index f866128..021abeb 100644 Binary files a/src/boot/boot.bin and b/src/boot/boot.bin differ diff --git a/src/boot/boot2.asm b/src/boot/boot2.asm index 25d4288..547de06 100644 --- a/src/boot/boot2.asm +++ b/src/boot/boot2.asm @@ -1,133 +1,473 @@ -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -; Stage 2 bootloader for ClassicOS ; -; -------------------------------- ; -; Loads the kernel, sets up tables, ; -; and transitions to protected mode ; -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; - -;;;;;;;;;;;;;;;;;;;;;;;; -; Assembler directives ; -;;;;;;;;;;;;;;;;;;;;;;;; - -; tells the assembler that the program will be loaded at 0x8000 -; this is done by the first stage bootloader -org 0x8000 - -; we are targeting (x86) 16-bit real mode -bits 16 - -;;;;;;;;;;;;;;;;; -; Jump to start ; -;;;;;;;;;;;;;;;;; -jmp start - -;;;;;;;; -; Data ; -;;;;;;;; -; kernel file name -kername db "KERNEL.BIN", 0 - -;;;;;;;;;;; -; Program ; -;;;;;;;;;;; - -start: - xor ax, ax ; set up segment registers to segment 0 since - mov ds, ax ; our addresses are already relative to 0x8000 - mov es, ax - - mov si, kername ; print kernel file name - call printstr - - ; Load the kernel into memory - %include "kernel_loader.asm" - - ; Set up IVT (GTD and IDT not used in 16 bit real mode) - ; Define interrupt handlers (replace with your actual handler code) - div_by_zero_handler: - cli - hlt - - timer_handler: - ; Your timer interrupt handler code - hlt - ret - - ; IVT entries (offset 0 for all handlers since segment 0) - times 0x100 dw 0x0000 ; Initialize unused entries - dw offset div_by_zero_handler ; Interrupt 0 (Division by Zero) - times 0x7 dw 0x0000 ; Skip unused entries - dw offset timer_handler ; Interrupt 0x8 (Timer) - - ; Switch to protected mode - ; Enable Protected Mode - switch_to_protected_mode: - cli ; Disable interrupts - mov eax, cr0 ; Get current CR0 value - or eax, 0x01 ; Set PE bit (Protected Mode Enable) - mov cr0, eax ; Write modified CR0 value back - - ; Set up stack and start executing kernel's code - ; Define GDT structure (replace with your actual GDT definition) - gdt_start: ; Beginning of GDT - times 5 dd 0 ; Null descriptor entries (optional) - gdt_code: ; Code segment descriptor - dw 0xffff ; Segment size (limit) - dw 0x0000 ; Segment base address (low) - db 0x0 ; Segment base address (high) - db 10011010b ; Access rights (present, readable, conforming, executable) - db 11001111b ; Access rights (long mode, 4-granularity, size) - gdt_end: ; End of GDT - gdt_descriptor: - equ gdt_end - gdt_start ; Size of GDT - dw gdt_descriptor ; Offset of GDT - dd gdt_start ; Base address of GDT - - ; Load the GDT - lgdt [gdt_descriptor] ; Load GDT descriptor into GDTR - - ; Set up Stack (replace with your actual stack segment and address) - mov ss, data_segment ; Set stack segment selector - mov esp, 0x100000 ; Set stack pointer (top of stack) - - ; Start Kernel Execution - jmp farptr kernel_entry ; Jump to kernel entry point (replace with actual address) - -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -; printstr routine, prints the string pointed by si using int 0x10 ; -; sets the direction flag to 0 ; -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -printstr: - cld ; clear df flag - lodsb increments si -printstr_loop: - 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 - -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -; halt routine - infinite loop ; -;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; -halt: - cli - jmp halt - -;;;;;;;;;;; -; Padding ; -;;;;;;;;;;; -; $ is the address of the current line, $$ is the base address for -; this program. -; the expression is expanded to 510 - ($ - 0x8000), or -; 510 + 0x8000 - $, which is, in other words, the number of bytes -; before the address 510 + 0x8000 (= 0x80FD), where the 0xAA55 -; signature shall be put. -times 510 - ($ - $$) db 0x00 - -;;;;;;;;;;;;;;;;;; -; BIOS signature ; -;;;;;;;;;;;;;;;;;; -dw 0xAA55 +[bits 16] +[org 0x7e00] + +start: + mov [bootdev], dl + +GetVesaControllerInfo: + ;Preset 1st 4 bytes of block with + ; 'VBE2' to get VBE2 information + + mov di, VESAControllerInfo + mov byte [di], 'V' + mov byte [di+1], 'B' + mov byte [di+2], 'E' + mov byte [di+3], '2' + + ;Function 00h: get VESA controller information + + mov ax, 0x4f00 + int 10h + + ;Get pointer to list of supported modes + mov ax, word [VESAControllerInfo+14] + + push ax + shr ax, 4 ;Grab segment of pointer + mov bx, ax ;and save it + + pop ax + and ax, 0x000f + + mov dx, word [VESAControllerInfo+16] ;pointer's offset + add dx, ax + + push es ;Save 'es' on stack + mov es, bx ;Segment + mov di, dx ;Offset + ; mov si, VESAControllerInfo ;Print VESA + ; call print + +save_available_video_modes: + mov bx, VbeModeList + +.save_modes_loop: ;Save all available modes + mov ax, word [es:di] + + cmp ax, 0xffff ;End of list? + je finished_mode_save + + mov [bx], ax ;Save mode number + + add bx, 2 + add di, 2 + jmp .save_modes_loop + +finished_mode_save: + mov [bx], ax + pop es + jmp short do_e820 + +mmap_ent equ mem_map_entries_count ; the number of entries will be stored at mem_map_entries_count + +do_e820: + pusha + push es + push bp + + mov ax, 0x3000 + mov es, ax + mov di, 0 + xor ebx, ebx ; ebx must be 0 to start + xor bp, bp ; keep an entry count in bp + mov edx, 0x0534D4150 ; Place "SMAP" into edx + mov eax, 0x0000e820 + mov [es:di + 20], dword 1 ; force a valid ACPI 3.X entry + mov ecx, 24 ; ask for 24 bytes + int 0x15 + jc short .failed ; carry set on first call means "unsupported function" + mov edx, 0x0534D4150 ; Some BIOSes apparently trash this register? + cmp eax, edx ; on success, eax must have been reset to "SMAP" + jne short .failed + test ebx, ebx ; ebx = 0 implies list is only 1 entry long (worthless) + je short .failed + jmp short .jmpin + +.e820lp: + 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 + mov ecx, 24 ; ask for 24 bytes again + int 0x15 + jc short .e820f ; carry set means "end of list already reached" + mov edx, 0x0534D4150 ; repair potentially trashed register + +.jmpin: + jcxz .skipent ; skip any 0 length entries + cmp cl, 20 ; got a 24 byte ACPI 3.X response? + jbe short .notext + test byte [es:di + 20], 1 ; if so: is the "ignore this data" bit clear? + je short .skipent + +.notext: + mov ecx, [es:di + 8] ; get lower uint32_t of memory region length + or ecx, [es:di + 12] ; "or" it with upper uint32_t to test for zero + jz .skipent ; if length uint64_t is 0, skip entry + inc bp ; got a good entry: ++count, move to next storage spot + add di, 24 + +.skipent: + test ebx, ebx ; if ebx resets to 0, list is complete + jne short .e820lp + +.e820f: + 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 + + mov dword [mem_map], 0x30000 ; the memory map is stored at this address + + pop bp + pop es + popa + jmp short load_kernel + +.failed: + mov si, memory_error + call print + jmp $ + +load_kernel: + + mov ah, 8 + mov dl, [bootdev] + int 13h ;Get drive params + + 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 + 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 \ No newline at end of file diff --git a/src/boot/boot2.bin b/src/boot/boot2.bin new file mode 100644 index 0000000..4707a0b Binary files /dev/null and b/src/boot/boot2.bin differ diff --git a/src/boot/kernel_loader.asm b/src/boot/kernel_loader.asm deleted file mode 100644 index 330eeee..0000000 --- a/src/boot/kernel_loader.asm +++ /dev/null @@ -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 \ No newline at end of file diff --git a/src/boot/linker.ld b/src/boot/linker.ld index b93be98..1b0294e 100644 --- a/src/boot/linker.ld +++ b/src/boot/linker.ld @@ -1,31 +1,25 @@ ENTRY(start) -SECTIONS { - . = 0x7c00; - - .text : { +SECTIONS +{ +.text : + { *(.text) } - .data : { +.data : + { *(.data) } - .bss : { +.bss : + { *(.bss) } - /* Define the bootloader signature at the end of the bootloader */ - bootloader_signature : { - *(.bootloader_signature) - } - - /* 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) +.kernel : + { + /* Kernel code */ + . = 0x9000; /* Start of kernel code section */ + *(.kernel) } } \ No newline at end of file diff --git a/src/cpu/cpuid.asm b/src/cpu/cpuid.asm index 1ec408c..213d83e 100644 --- a/src/cpu/cpuid.asm +++ b/src/cpu/cpuid.asm @@ -3,16 +3,30 @@ global cpuid cpuid: - ; Input parameter in EAX register - mov eax, %edi + ; Save registers + push ebp + mov ebp, esp + push ebx + push edi + push esi - ; Call CPUID instruction (clobbers EAX, EBX, ECX, EDX) - cpuid + ; Input parameter in EAX register + mov eax, [ebp + 8] ; Assuming the input is passed on the stack - ; Return values in output registers - mov %esi, [esp + 4] ; eax (output) - mov %edx, [esp + 8] ; ebx (output) - mov %ecx, [esp + 12] ; ecx (output) - mov %edi, [esp + 16] ; edx (output) + ; Call CPUID instruction (clobbers EAX, EBX, ECX, EDX) + cpuid - 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 \ No newline at end of file diff --git a/src/drivers/bus/eisa.c b/src/drivers/bus/eisa.c index b9a809c..c05f040 100644 --- a/src/drivers/bus/eisa.c +++ b/src/drivers/bus/eisa.c @@ -1,118 +1,137 @@ -#include "eisa.h" - -#include -#include -#include -#include - -#define MY_DEVICE_VENDOR_ID 0x1234 -#define MY_DEVICE_DEVICE_ID 0x5678 -#define MY_DEVICE_CLASS_CODE 0x90AB - -// EISA bus controller base address -#define EISA_BASE_ADDRESS 0x0000 - -// EISA bus controller data port -#define EISA_DATA_PORT 0x00 - -// EISA bus controller command port -#define EISA_COMMAND_PORT 0x01 - -// Initialize the EISA bus -void eisa_init() -{ - // Add any necessary initialization code here -} - -// Detect and configure EISA devices -void eisa_detect_devices() -{ - uint32_t bus, slot, func; - uint16_t vendor_id, device_id, class_code; - - for (bus = 0; bus < 256; bus++) - { - for (slot = 0; slot < 32; slot++) - { - for (func = 0; func < 8; func++) - { - uint32_t address = (bus << 16) | (slot << 11) | (func << 8); - uint32_t id = eisa_read_config_dword(address, 0); - vendor_id = id & 0xFFFF; - device_id = (id >> 16) & 0xFFFF; - class_code = eisa_read_config_word(address, 10); - if (vendor_id != 0xFFFF) - { - // Device detected, do something with it - if (vendor_id == MY_DEVICE_VENDOR_ID && - device_id == MY_DEVICE_DEVICE_ID && - class_code == MY_DEVICE_CLASS_CODE) - { - // This is my device, configure it - uint32_t config1 = eisa_read_config_dword(address, 4); - uint32_t config2 = eisa_read_config_dword(address, 8); - //printf("Config1: %u\n", config1); - //printf("Config2: %u\n", config2); - // Do something with the configuration data - } - } - } - } - } -} - -// 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) -{ - // Set the EISA bus controller base address - eisa_write(EISA_BASE_ADDRESS, address); - - // Set the EISA bus controller command port to read configuration data - eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03)); - - // Read the double word from the EISA bus controller data port - uint32_t value = 0; - 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 -uint16_t eisa_read_config_word(uint32_t address, uint8_t offset) -{ - // Set the EISA bus controller base address - eisa_write(EISA_BASE_ADDRESS, address); - - // Set the EISA bus controller command port to read configuration data - eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03)); - - // Read the word from the EISA bus controller data port - uint16_t value = 0; - for (int i = 0; i < 2; i++) - { - value |= (eisa_read(EISA_DATA_PORT) << (i * 8)); - } - - 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)); -} \ No newline at end of file +#include "eisa.h" + +#include +#include +#include +#include + +#define MY_DEVICE_VENDOR_ID 0x1234 +#define MY_DEVICE_DEVICE_ID 0x5678 +#define MY_DEVICE_CLASS_CODE 0x90AB + +// EISA bus controller base address +#define EISA_BASE_ADDRESS 0x0000 + +// EISA bus controller data port +#define EISA_DATA_PORT 0x00 + +// EISA bus controller command port +#define EISA_COMMAND_PORT 0x01 + +// Initialize the EISA bus +void eisa_init() +{ + // Add any necessary initialization code here +} + +// Detect and configure EISA devices +void eisa_detect_devices() +{ + uint32_t bus, slot, func; + uint16_t vendor_id, device_id, class_code; + + for (bus = 0; bus < 256; bus++) + { + for (slot = 0; slot < 32; slot++) + { + for (func = 0; func < 8; func++) + { + uint32_t address = (bus << 16) | (slot << 11) | (func << 8); + uint32_t id = eisa_read_config_dword(address, 0); + vendor_id = id & 0xFFFF; + device_id = (id >> 16) & 0xFFFF; + class_code = eisa_read_config_word(address, 10); + if (vendor_id != 0xFFFF) + { + // Device detected, do something with it + if (vendor_id == MY_DEVICE_VENDOR_ID && + device_id == MY_DEVICE_DEVICE_ID && + class_code == MY_DEVICE_CLASS_CODE) + { + // This is my device, configure it + uint32_t config1 = eisa_read_config_dword(address, 4); + uint32_t config2 = eisa_read_config_dword(address, 8); + + //printf("Config1: %u\n", config1); + //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); + } + + if (config1 & 0x00000010) { + // Set DMA channel based on bits 4-5 of config1 + uint8_t dma_channel = (config1 >> 4) & 0x03; + eisa_write(0xspecific_port_2, dma_channel); + } + + // Check for specific bits in config2 + if (config2 & 0x00000001) { + // Configure interrupt line based on bit 0 of config2 + eisa_write(0xspecific_port_3, 0xinterrupt_line_number); + } + } + } + } + } + } +} + +// 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) +{ + // Set the EISA bus controller base address + eisa_write(EISA_BASE_ADDRESS, address); + + // Set the EISA bus controller command port to read configuration data + eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03)); + + // Read the double word from the EISA bus controller data port + uint32_t value = 0; + 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 +uint16_t eisa_read_config_word(uint32_t address, uint8_t offset) +{ + // Set the EISA bus controller base address + eisa_write(EISA_BASE_ADDRESS, address); + + // Set the EISA bus controller command port to read configuration data + eisa_write(EISA_COMMAND_PORT, 0x80 | (offset & 0x03)); + + // Read the word from the EISA bus controller data port + uint16_t value = 0; + for (int i = 0; i < 2; i++) + { + value |= (eisa_read(EISA_DATA_PORT) << (i * 8)); + } + + 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)); +} diff --git a/src/filesystem/fat16/fat16.c b/src/filesystem/fat16/fat16.c index 6cde96b..a926264 100644 --- a/src/filesystem/fat16/fat16.c +++ b/src/filesystem/fat16/fat16.c @@ -1,16 +1,27 @@ #include "fat16.h" #include #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) int read_sector(uint32_t sector_number, void *buffer) { // ... (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, §or, &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) { - 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) diff --git a/src/filesystem/fat16/fat16.h b/src/filesystem/fat16/fat16.h index 3ebd6c6..9ad3441 100644 --- a/src/filesystem/fat16/fat16.h +++ b/src/filesystem/fat16/fat16.h @@ -2,6 +2,9 @@ #define FAT16_H #include + +#include "../../ata.h" + // Define constants for sector size, cluster size, etc. (replace with actual values) #define SECTOR_SIZE 512 #define BYTES_PER_CLUSTER 4096 // Example: 8 sectors per cluster diff --git a/src/filesystem/fat16/fat16_io.c b/src/filesystem/fat16/fat16_io.c index b8608cd..6f768e6 100644 --- a/src/filesystem/fat16/fat16_io.c +++ b/src/filesystem/fat16/fat16_io.c @@ -1,5 +1,7 @@ #include "fat16_io.h" #include +#include "src/kernel/arch/x86/disk/ata.h" +#include "fat16.h" // I/O port addresses for IDE controller (replace with actual values if needed) #define PRIMARY_DATA_REGISTER 0x1F0 #define PRIMARY_ERROR_REGISTER 0x1F1 diff --git a/src/filesystem/fat16/fat16_io.h b/src/filesystem/fat16/fat16_io.h index 7a6bf6b..390f0d2 100644 --- a/src/filesystem/fat16/fat16_io.h +++ b/src/filesystem/fat16/fat16_io.h @@ -2,6 +2,8 @@ #define FAT16_IO_H #include +#include "fat16.h" +#include "src/kernel/arch/x86/disk/ata.h" // I/O port addresses for IDE controller (replace with actual values if needed) #define PRIMARY_DATA_REGISTER 0x1F0 diff --git a/src/kernel/arch/x86/disk/ata.h b/src/kernel/arch/x86/disk/ata.h new file mode 100644 index 0000000..50fde48 --- /dev/null +++ b/src/kernel/arch/x86/disk/ata.h @@ -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 diff --git a/src/kernel/kernel.c b/src/kernel/kernel.c index 862ed3e..d948bbe 100644 --- a/src/kernel/kernel.c +++ b/src/kernel/kernel.c @@ -1,4 +1,8 @@ #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 #include #include @@ -45,6 +49,13 @@ void init_devices() { // 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() { clear_screen(); print("Welcome to ClassicOS!"); @@ -52,6 +63,16 @@ void kernel_main() { // Initialize 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 init_devices(); @@ -70,4 +91,3 @@ void kernel_main() { handle_system_calls(); } } - diff --git a/src/kernel/kernel.h b/src/kernel/kernel.h index 1dc902c..db36ac8 100644 --- a/src/kernel/kernel.h +++ b/src/kernel/kernel.h @@ -1,7 +1,4 @@ #ifndef KERNEL_H #define KERNEL_H -// Function to print a null-terminated string to the screen -void print_string(const char* str); - #endif \ No newline at end of file diff --git a/src/kernel/malloc/kmalloc.h b/src/kernel/malloc/kmalloc.h index bd88c5c..b411d17 100644 --- a/src/kernel/malloc/kmalloc.h +++ b/src/kernel/malloc/kmalloc.h @@ -1,12 +1,24 @@ -#ifndef KMALLOC_H_ // Corrected guard macro -#define KMALLOC_H_ +#ifndef KMALLOC_H +#define KMALLOC_H -#include // For size_t +#include +#include -void *kmalloc(size_t size); -void kfree(void *ptr); +// Structure to represent a memory block in the kernel heap +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); -void mark_as_free_kernel(void *ptr); +// Function prototypes +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_ */