diff --git a/src/@bootsec.asm b/src/@bootsec.asm deleted file mode 100644 index cb3fd0e..0000000 --- a/src/@bootsec.asm +++ /dev/null @@ -1,316 +0,0 @@ -base equ 0x7C00 - org base - - ; boot sector identification bytes: - jmp short init ; EB3C - nop ; 90 - - ; OEM vendor field -vendor .space 8, 0x20 - ; bios parameter block -ss .space 2 ; word bytes per sector -sc .space 1 ; byte sectors per cluster -rsc .space 2 ; word reserved sector count -fn .space 1 ; byte number of fat tables -rde .space 2 ; word root disk entries -ts .space 2 ; word total sectors -md .space 1 ; byte media descriptor byte -fs .space 2 ; word sectors per fat -spt .space 2 ; word sectors per track -nos .space 2 ; word number of sides/heads -hs .space 4 ; dword partition offset -lts .space 4 ; dword large total sectors - ; extended bios parameter block data - .space base+03Eh-$ - -init xor ax, ax ; ax as quick zero value - ; initialize all segment registers - ; the docs say we cant rely on them to have any sensible values - ; we only work with the first 64kB per default - ; so we set all of them to zero - mov ds, ax - mov es, ax - mov ss, ax - mov sp, ax - jmp main - - ; print AX in base BX - ; destroys DX -putnum xor dx, dx - div bx - test cx, cx - loopnz .pad - test ax, ax - je .nib -.pad push dx - call putnum - pop dx - ; print lower DL as digit -.nib add dl, 0x30 - cmp dl, 0x3a - jl putc - add dl, 7 - ; print DL as char -putc mov ah, 0x0e - mov al, dl - int 0x10 - ret - - ; print str at SI - ; NUL-terminated -puts lodsb - test al, al - jz .l01 - mov dl, al - call putc - jmp puts -.l01 ret - - ; print a newline -newlin mov dl, 0x0A - call putc - mov dl, 0x0D - jmp putc - - ; print register set - ; order AX CX DX BX BP SI DI IP - ; trashes flags -debug push di - push si - push bp - push bx - push dx - push cx - push ax - mov si, sp - call dump - pop ax - pop cx - pop dx - pop bx - pop bp - pop si - pop di - ret - - ; dump the 8 words at SI -dump lea di, [si+16] - mov bx, 0x10 -.loop lodsw - mov cx, 4 - call putnum - mov dl, 020h ; space char - call putc - cmp si, di - jc .loop - jmp newlin - - ; Advantages over using int13h directly: - ; - Translation from linear sector number into CHS data - ; - Reads across different tracks. - ; Older BIOSes don't support that. - ; - Nearby sector reads/writes are coalesced into one int 13h call - ; This improves performance on real hardware. - ; Only floppies are supported, and only variants with two sides - ; This includes the standard 5 1/4 360kB and 3 1/2 1.44MB formats - - ; When a sector is requested, int13h is not called yet, the parameters - ; for int 13h are recorded. When the next sector is requested, either - ; it it suitable for coalescing, then the recorded parameters are - ; adjusted. When the sector is not suitable for coalescing, the - ; previous sector is read/written and the parameters for the new - ; sector are put into the record. If the program is done with listing - ; the wanted sectors, another function can be called to force doing - ; the recorded io request - - ; Select a sector for a disk operation - ; IN ax linear sector number - ; cx number of sectors to read/write - ; dl drive number -sector push ax - push cx - - ; split up sector number into CHS data - ; divisor is sectors per track field in bios parameter block - ; quotient al as track number - ; remainder ah as sector number (starting with 0) - div byte [spt] - ; phys sector number cl (starting with 1) - mov cl, ah - inc cl - - ; get head number dh from lowest bit of track number - ; hard-coded assumption: two-sided floppy - mov dh, al - and dh, 1 - - ; cylinder number ch is track number, except the head number shifted out - mov ch, al - shr ch, 1 - - ; Unlucky if different head (dh) - cmp byte dh, [disk_dh] - jne .miss - ; Unlucky if different track (ch) or not subsequent sector (cl + number of op sectors) - mov ax, cx - sub al, [disk_al] - cmp ax, [disk_cx] - jne .miss - ; We are lucky! We can extend the current request by increasing the number of op sectors - ; Do nothing else - inc byte [disk_al] - jmp .end - - ; The sector we just selected does not fit into the recorded io request - ; So we submit that request first and then record a new io request -.miss: push cx - push dx - call diskio - pop dx - pop cx - ; Record new io request - mov word [disk_cx], cx - mov byte [disk_dh], dh - mov byte [disk_al], 1 ; only one sector yet -.end pop cx - pop ax - inc ax - loop sector - ret - - ; Do the io request we recorded previously now -diskio mov ax, [disk_ax] - mov cx, [disk_cx] - mov dx, [disk_dx] - mov bx, [disk_bx] - - ; no-op if amount of sectors is zero - cmp al, 0 - je .ret - - ; TODO: retry is needed for real floppies - call debug - int 0x13 - jc .ret - - ; Advance read/write pointer in memory - mov ah, 0 - mov cl, 9 - shl ax, cl - add word [disk_bx], ax - - ; Reset op sector length, work done - mov byte [disk_al], 0 - -.ret ret - - ; Load a file from disk to 0x7C00 - ; calculate size of the directory in sectors -load: mov ax, [rde] - mov cl, 4 ; sector=512b, entry=32b -> shift 4 bits - shr ax, cl - mov cx, ax - push cx ; remember number of dir entries for later - - ; calculate start of second fat table - mov ax, [fs] ; read fat table length - push ax - add cx, ax ; make cx size of FAT + dir - inc ax ; add one for the boot sector - - ; Read second FAT and directory into buffer - mov byte [disk_ah], 2 ; set read OP - mov word [disk_bx], fatbuf ; write into our own buffer - call sector - call diskio - - ; get address of root directory in frame - pop bx - mov cl, 9 - shl bx, cl - add bx, fatbuf - - pop dx - - mov word [disk_bx], 0x7C00 - - ; search through root directory -.loop: mov si, bx - mov ax, [bx+0x1A] - mov di, fname - mov cx, 11 - repe cmpsb - je .cloop - add bx, 0x20 - or byte [bx], 0 - jz .end - jmp .loop - - ; calculate sector offset in cluster area -.cloop push ax - sub ax, 2 - mov ch, 0 - mov cl, [sc] - push cx - mul cx - ; calculate sector offset from root directory - mov dx, [rde] - mov cl, 4 ; sector=512b, entry=32b -> shift 4 bits - shr dx, cl - add ax, dx - ; add length of fat tables - add ax, [fs] - add ax, [fs] - ; plus 1 for the boot sector - inc ax - ; load cluster - pop cx - call sector - ; follow fat chain - pop ax - mov si, ax - shr si, 1 - add si, ax - mov dx, [fatbuf+si] - ; shift value if needed - test ax, 1 - jz .noshr - mov cl, 4 - shr dx, cl -.noshr and dx, 0x0FFF - mov ax, dx - cmp ax, 0xFF0 - jc .cloop - -.fend: call diskio - -.end: ret - -main: mov byte [disk_dl], dl - call load - - db 0xEA ; jmp far 0:0x7C00 - dw 0x7C00, 0 - - ; register buffer for disk io -disk_al db 0 ; number of sectors to read -disk_ah db 2 ; 2=read op -disk_cl db 1 ; sector number -disk_ch db 1 ; cylinder number -disk_dl db 0 ; drive number -disk_dh db 0 ; head number -disk_bx dw fatbuf ; data buffer addr, advanced by 'diskio' - -disk_ax equ disk_al -disk_cx equ disk_cl -disk_dx equ disk_dl - -fname db "@RDOS ", "COM" - - .space base+01FEh-$ - dw 0xAA55 - - ; buffer for fat table and root directory - ; we load it together to save an int 13h read - ; at the cost of having to calculate offset of rootdir -fatbuf equ $ diff --git a/src/@rdos.asm b/src/@rdos.asm index 13a1387..0afc174 100644 --- a/src/@rdos.asm +++ b/src/@rdos.asm @@ -1,18 +1,633 @@ - org 600h + org 0x700 +cseg equ 0x0 - jmp end +%include "version.inc" - add [bx+si], al - add al, al - add ax, ax - rep movsb - cs xor word [bp], 0x7C00 - xor word [bp+04h], 0x7C00 - lock es xor word [04h], 0x7C00 + jmp _entry +banner db "RDOS KERNEL 1.0", 0x0A, 0x0D, '$', 0x1A +_entry call .l01 +.l01 pop ax + sub ax, .l01 + mov cl, 4 + shr ax, cl + mov cx, cs + add cx, ax + push cx + mov ax, start + push ax + retf - dw foo +;;; Character I/O -end hlt - jmp end + ; direct console I/O + ; IN dl character to output or 0xFF if input + ; OUT al character to read +conio cmp dl, 0xFF + je conin -foo equ end+040h + ; raw console output + ; IN dl character +conout xchg ax, dx + mov ah, 0x0e + mov bx, 7 + int 0x10 + ret + + ; read character from console + ; OUT al character or zero +conin call const + test al, al + jz .ret + mov al, 0 + int 0x16 +.ret ret + + ; check if character has characters ready + ; OUT al 0xFF if data, 0 if none +const mov ah, 1 + int 0x16 + jz .emp + mov ax, 0xFF + ret +.emp mov al, 0 + ret + + ; dummy: write to auxillary dev +auxout ret + + ; dummy: read from auxillary dev +auxin mov al, 0x1A + ret + + ; dummy: lister out +lstout ret + + ; character input with echo + ; OUT al character +getc call const + test al, al + jz getc + call conin + push ax + mov dl, al + call putc + pop ax + ret + + ; character input without echo +readc call const + test al, al + jz readc + jmp conin + + ; character output + ; IN dl character +putc jmp conout + + ; output character string + ; IN ds:dx far ptr to string, '$'-terminated +puts push si + mov si, dx +.loop lodsb + cmp al, '$' + je .ret + mov dl, al + call putc + jmp .loop +.ret pop si + ret + + ; send a beep ctl to console +beep mov dl, 0x07 + jmp conout + + ; buffered input + ; IN ds:dx far ptr to buffer +gets mov si, dx + mov cx, [si] + mov ch, 0 + ; ch = actual number of chars + ; cl = maximum number of chars +.loop call readc + cmp al, 0x0D + je .cr + cmp al, 0x08 + je .bs + cmp al, 0x20 + jc .loop + ; check if there is space in the buffer + ; emit a beep if not + mov dl, cl + dec dl + cmp ch, dl + jc .append + call beep + jmp .loop + ; append to buffer +.append mov bh, 0 + mov bl, ch + mov [si+2+bx], al + inc ch + mov dl, al + call putc + jmp .loop + ; handle backspace +.bs: test ch, ch + jz .loop + mov dl, 0x08 + call putc + mov dl, 0x20 + call putc + mov dl, 0x08 + call putc + dec ch + jmp .loop + ; handle carriage return +.cr mov bx, 0 + mov bl, ch + mov [si+2+bx], al + mov [si], cx + mov dl, 0x0A + call putc + mov dl, 0x0D + call putc + ret + +;;; System functions + + ; Return OS version from version.inc +ver mov bx, bdosver | 0x1000 + ret + +;;; Disk i/o + +%include "bpb.inc" + + ; dflags bitfields +DRVLOG equ 0x01 ; bit 0 - drive logged in (see drvnum) +DRVCTL equ 0x02 ; bit 1 - controller configured +DRVEXT equ 0x04 ; bit 2 - EBIOS supported +DIRTY equ 0x08 ; bit 3 - dskbuf dirty +DRVCHS equ 0x10 ; bit 4 - CHS geometry known + + ; Wrapper around int 13h +int13 int 0x13 + ; TODO: on error: reset & retry + ; TODO: record errors + ; TODO: multi-track reading + ; TODO: handle DMA boundaries + ret + + ; get drive parameters + ; read BIOS int13h/AH=8 values + ; DPT data gets copied over our dpt + ; CHS data gets inserted into our bpb +getprm test byte [dflags], DRVEXT + jnz .ret + ; fallback non-zero values (5 1/4", 160kB) + mov word [drvspt], 8 + mov word [drvspc], 8 + ; do the query + mov ah, 8 + mov dl, [biosnum] + call int13 + ; bail out if error + jc .ret + ; ignore CHS values if odd + test cl, cl + jz .nochs + ; get and store sector number + and cx, 0x3F + mov word [drvspt], cx + ; get and store number heads + xchg dl, dh + and dx, 0xFF + inc dx + ; multiply with sectors per track + mov ax, dx + mul cx + ; store sectors per cylinder + mov [drvspc], ax + ; test if DPT ptr is non-zero +.nochs mov ax, es + or ax, di + test ax, ax + jz .ret + ; copy BIOS dpt table over ours + ;mov dx, dpt + ;mov bx, di + ;mov cx, 11 + ;call lodfar +.ret ret + + ; select a drive for io + ; IN dl drive number + ; dont do anything if drive already selected +select cmp dl, [drvnum] + je getprm.ret + ; clear out current contents + push dx + call flush + mov ax, 0xFFFF + mov [drvseek], ax + mov [drvseek+2], ax + and word [dflags], ~(DRVLOG|DRVCTL|DRVEXT|DIRTY|DRVCHS) + pop dx + ; set current drive number + mov [drvnum], dl + ; fork off if hdd + cmp dl, 2 + jnc loghdd + +logfdd mov [biosnum], dl + and dx, 0x0D + ; query bios for geometry and DPT + call getprm + ; assume 512 bytes per sector + ; TODO: read this from DPT + mov byte [drvss], 2 + ; fill partition offset with zeroes + xor ax, ax + mov di, drvoff + stosw + stosw + ; fill partition end with 1's + not ax + stosw + stosw + ; shared code with loghdd + jmp rdbpb + + ; Log in a drive on a hard disk + ; IN dl bits 0-1: partition number + ; bits 2-7: drive number + ; Partition offset is read from MBR + ; split drive & partition number +loghdd mov dh, dl + and ah, 0x3 + shr dl, 1 + shl dl, 1 + add dl, 0x80 + ; partition number in DH + mov byte [biosnum], dl + push dx + ; test for EBIOS extensions + mov ah, 0x41 + mov bx, 0x55AA + call int13 + sbb bx, 0xAA55 + jnz .noeb + ; enable EBIOS and assume controller is configured + or word [dflags], DRVCTL | DRVEXT + ; hard disks are always assumed to be 512 bytes / sector +.noeb mov byte [drvss], 2 + ; query BIOS for geometry + call getprm + or word [dflags], DRVCHS + ; read MBR + xor ax, ax + xor dx, dx + call map + ; get partition number + pop bx + xor bh, bh + mov cl, 4 + sal bx, cl + ; bail out if partition undef + cmp byte [dskbuf+0x1be+bx+4], 0 + je .ret + ; load partition offset + mov ax, [dskbuf+0x1be+bx+8] + mov dx, [dskbuf+0x1be+bx+8+2] + ; store partition offset + mov [drvoff], ax + mov [drvoff+2], dx + ; add partition length + add ax, [dskbuf+0x1be+bx+12] + adc dx, [dskbuf+0x1be+bx+12+2] + ; partitions after 4 TB mark not allowed + jc .ret + ; store partition end + mov [drvend], ax + mov [drvend+2], dx +.ret ret + + ; parse bios parameter block from drvoff + ; drvoff and biosnum need to be set up +rdbpb mov ax, [drvoff] + mov dx, [drvoff+2] + call map + ; read partition start + mov ax, [drvoff] + mov dx, [drvoff+2] + ; add reserved sectors + add ax, [dskbuf+BPBOFF+BPBRSC] + adc dx, 0 + jc .ret + ; save offset of fat table + mov [drvfat], ax + mov [drvfat+2], dx + ; calculate length of all fat tables + mov ah, 0 + mov al, [dskbuf+BPBOFF+BPBFN] + mov dx, [dskbuf+BPBOFF+BPBFS] + mov [drvfn], dx + mul dx + add ax, [drvfat] + adc dx, [drvfat+2] + ; save offset of root directory + mov [drvrd], ax + mov [drvrd+2], dx + ; calculate length of root directory + mov ax, [dskbuf+BPBOFF+BPBRDE] + mov cl, [drvss] + add cl, 2 + shr ax, cl + ; read offset to cluster area + ; read cluster size +.ret ret + + ; map sector into dskbuf + ; skip doing a read if sector number matches + ; IN dx:ax absolute sector number +map cmp ax, [drvseek] + jne .do + cmp dx, [drvseek+2] + jne .do + ret + ; flush previous contents +.do push ax + push dx + call flush + pop dx + pop ax + ; set sector number + mov [drvseek], ax + mov [drvseek+2], dx + ; issue read cmd + mov ch, 2 + jmp diskio + + ; mark dskbuf as containing unwritten changes +dirty or word [cs:dflags], DIRTY +l002 ret + + ; flush buffer if dirty +flush test word [cs:dflags], DIRTY + jz l002 + ; issue write cmd + mov ch, 3 + + ; Do disk I/O + ; IN ch 2 = read + ; 3 = write + ; Sector number is read from [drvseek] +diskio mov cl, 1 ; read len + ; DS := ES := CS + mov ds, [cs:dseg] + ; check if ebios supported + test word [dflags], DRVEXT + jz .noext + ; set up regs for ebios call + xchg ax, cx + or ah, 0x40 + jmp .do + ; check if we can skip controller reset +.noext test word [dflags], DRVCTL + jnz .norst + ; do controller reset + mov dl, [biosnum] + mov ah, 0 + call int13 + or word [dflags], DRVCTL + ; put linear sector num into dx:ax +.norst mov ax, [drvseek] + mov dx, [drvseek+2] + ; dx:ax = linear count + div word [drvspc] + ; TODO: is it possible to get an overflow here? + xchg ax, dx + ; dx = cylinder, ax = head * spt + sector + div byte [drvspt] + ; dx = cylinder, al = head, ah = sector + xchg ax, dx + xchg al, ah + ror al, 1 + ror al, 1 + or al, dh + inc ax + ; dl: head number + ; ah bit 0-7: cylinder bits 0-7 + ; al bit 0-5: sector bits 0-5 + ; al bit 6-7: cylinder bits 8-9 + ; shuffle values around for bios + xchg ax, cx + xchg dh, dl +.do mov dl, [biosnum] + ; ah: subfunction selected via cx previously + ; al: 1 = reading 1 sector + ; cx: sector and cylinder number + ; dh: head number + ; dl: drive number + push es + push si + mov si, dap + les bx, [si+4] + call int13 + pop si + pop es + jc .err + ; clear dirty flag on success + and word [dflags], ~DIRTY + clc + ret + ; assume controller is misconfigured +.err and word [dflags], ~DRVCTL + ; exit with carry flag set + stc + ret + +;;; Export functions as syscalls +; SP, BP, SI, DI and ES must be preserved by kernel code +; DL, DX or DS:DX is input argument from prog +; AL, BX or ES:BX is return value to prog + +srb equ 0x8000 +srw equ 0x4000 + +; DOS style syscall interface +int21h push bx + xor bx, bx + mov bl, ah + jmp sysc + +; CP/M-86 style syscall interface +intE0h push bx + xor bx, bx + mov bl, cl + + ; bx = syscall number + ; stack must be -> BX IP CS FL + ; for return to prog +sysc sti + cld + add bx, bx + mov bx, [cs:bx+stab] + test bh, srw >> 8 ; fork off bx returns + jnz .l02 + test bh, srb >> 8 ; fork off al returns + jnz .l01 + ; syscall with no return value + push dx + push cx + push ax + push ds + call bx + pop ds + pop ax + pop cx + pop dx + pop bx + iret + ; syscalls returning byte in al +.l01 push dx + push cx + push ds + and bh, ~(srb >> 8) + call bx + pop ds + pop cx + pop dx + pop bx + iret + ; syscalls returning bx or es:bx +.l02 add sp, 2 ; discard bx on the stack + push dx + push cx + push ax + push ds + and bh, ~(srw >> 8) + call bx + pop ds + pop ax + pop cx + pop dx + ret + +start xor ax, ax + mov ds, ax + + ; install int20h handler + mov word [4*0x20], start + mov [4*0x20+2], cs + ; install int21h handler + mov word [4*0x21], int21h + mov [4*0x21+2], cs + ; install intE0h handler + mov word [4*0xE0], intE0h + mov [4*0xE0+2], cs + + mov ax, cs + mov ds, ax + mov [dseg], ax + + ; print banner + mov dx, banner + call puts + + ; read cmdline + mov dl, '>' + call putc + mov dx, inbuf + mov byte [inbuf], 72 + call gets + +halt sti + hlt + jmp halt + +section .rodata + + ; syscall table +stab dw 0 ; 0 reboot + dw getc + srb ; 1 console input + dw putc ; 2 console output + dw auxin ; 3 reader in + dw auxout + srb ; 4 puncher out + dw lstout ; 5 lister out + dw 0 ; 6 direct console i/o + dw 0 ; 7 read i/o byte + dw 0 ; 8 get i/o byte + dw puts ; 9 string output + dw gets ; 10 string input + dw 0 ; 11 console status + dw ver ; 12 get version number + dw 0 ; 13 reset disks + dw 0 ; 14 set drive + dw 0 ; 15 open file + dw 0 ; 16 close file + dw 0 ; 17 find first + dw 0 ; 18 find next + dw 0 ; 19 delete file + dw 0 ; 20 sequential read + dw 0 ; 21 sequential write + dw 0 ; 22 create file + dw 0 ; 23 rename file + dw 0 ; 24 get login vector + dw 0 ; 25 get drive + dw 0 ; 26 set dma addr + dw 0 ; 27 alloc vector + dw 0 ; 28 set drive r/o + dw 0 ; 29 get r/o vector + dw 0 ; 30 file attr + dw 0 ; 31 get addr of disk parameter block + dw 0 ; 32 get user number + dw 0 ; 33 random read + dw 0 ; 34 random write + dw 0 ; 35 calculate file size + dw 0 ; 36 calculate cur record number + dw 0 ; 37 reset drive + dw 0 ; 38 + dw 0 ; 39 + dw 0 ; 40 random write with block init +stab_e nop + +section .data + +dap db 0x10, 0 + dw 1 + dw dskbuf +dseg dw 0 +drvseek dw 0,0,0,0 + + ; bit 0 (1) - drive logged in (see drvnum) + ; bit 1 (2) - controller configured + ; bit 2 (4) - EBIOS supported + ; bit 3 (8) - dskbuf dirty +dflags dw 0 + +section .bss + + ; drive currently logged in +drvnum resb 1 + ; number, just for bios +biosnum resb 1 + +; Information for logged in drive +drvss resb 1 ; sector size, 2^(7+n) bytes +drvcs resb 1 ; cluster size, 2^(7+n) bytes + alignb 4 +drvspt resb 2 ; sectors per track +drvspc resb 2 ; sectors per cylinder +drvoff resb 4 ; partition offset +drvend resb 4 ; first sector after the partition +drvfat resb 4 ; offset to fat table +drvrd resb 4 ; offset of root directory +drvcla resb 4 ; offset to cluster area +drvfn resb 2 ; sectors per fat table + + ; disk buffer for I/O operations + alignb 2 +dskbuf resb 1024 + +inbuf resb 128 diff --git a/src/hello.asm b/src/hello.asm index d8469cc..3e6579b 100644 --- a/src/hello.asm +++ b/src/hello.asm @@ -2,14 +2,14 @@ ; This is primarily for testing purposes org 0x0100 -main mov si, str +main: mov si, string mov ah, 0x0e xor bx, bx -main1 lodsb +.loop: lodsb test al, al - jz main2 + jz .end int 0x10 - jmp main1 -main2 ret + jmp .loop +.end: ret -str db "Hello world!", 0x0A, 0x0D, 0 +string: db "Hello world!", 0x0A, 0x0D, 0