Page 1 of 1

Keyboard handler problem

Posted: Mon Sep 23, 2002 6:14 pm
by AlanO
hey,
my keyboard asm code:
ReadLoop: mov ah, 0 ;Read Key opcode
int 16h
cmp al, 0 ;Special function?
jz ReadLoop ;If so, don't echo this keystroke
putc
cmp al, 0dh ;Carriage return (ENTER)?
jne ReadLoop



reboots my computer when called from a c function, i believe it has to be somehting wrong with my bootloader, but what could it be?
thanks so much in advanced
Alan

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 6:44 pm
by dronkit
putc works fine?

are you working in pmode or rmode?

can you dump or know-for-sure the contents of cs/ds?

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 7:04 pm
by AlanO
protected mode
putc probably dones't work lol
and um, i dunno

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 7:08 pm
by dronkit
you know, you can't call BIOS functions directly from pmode...

either you go back to rmode and then back to pmode or you are sure your in unreal mode

did you set your stack to 16 or 32 bits? what about your code descriptor?

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 7:15 pm
by AlanO
   %include "gdt.inc"

   struc   BB      ;FAT Boot block
      resb   0xD   ;Things we ignore
BB_clu      resb   1   ;Sectors per cluster
BB_res      resw   1   ;Reserved sectors
BB_fats      resb   1   ;Number of FATs
BB_root      resw   1   ;Root directory entries
      resb   3   ;Things we ignore
BB_fat      resw   1   ;Sectors per fat
BB_sec      resw   1   ;Sectors per track
BB_head      resw   1   ;Heads
   endstruc

SEGMENT   START USE16

;> cs = 0
;>> dl = drive we were booted from

boot:   jmp short start         ;Standard start of boot sector
   nop
   resb   0x3B         ;Skip over parameters (set by format)

start:




   cli            ;{0} Disable Interrupts
   lgdt   [cs:gdt]      ;Load GDT
   mov   ecx, CR0      ;Switch to protected mode
   inc   cx
   mov   CR0, ecx      ;{5}
.5:   in   al, 0x64      ;Enable A20 {4A}
   test   al, 2
   jnz   .5
   mov   al, 0xD1
   out   0x64, al
.6:   in   al, 0x64
   and   ax, byte 2
   jnz   .6
   mov   al, 0xDF
   out   0x60, al

;> ah = 0
;> dl = drive we were booted from

   mov   al, flat_data      ;Selector for 4Gb data seg
   mov   ds, ax         ;{2} Extend limit for ds
   mov   es, ax         ;Extend limit for es
   dec   cx         ;Switch back to real mode
   mov   CR0, ecx      ;{5}

   mov   [boot], dl      ;Save drive number we came from
   mov   sp, 0x800      ;{1B}

   xor   eax, eax      ;Segment
   mov   ds, ax         ;
   mov   ss, ax
   mov   es, sp         ;Read directory at 800:0 {1C}

;> eax = 00000000

   mov   al, [boot+BB_fats]   ;Number of FATs
   mul   byte [boot+BB_fat]   ;Times size of FAT
   add   ax, [boot+BB_res]   ;Plus Sectors before first FAT
               ;eax = LBN of Root directory
   movzx   edi,word [boot+BB_root]   ;Root directory entries
   push   di         ; used again later
   dec   di         ;Convert to number of sectors
   shr   di, 4         ; 16 directory entries per sector
   inc   di
   call   read_sectors

;> eax = LBN of root directory
;> edi = length of root directory in sectors
;> [sp] = length of root directory in entries
;> esi = 00000000

   lea   ebp, [eax+edi]      ;ebp = LBN of cluster 2

   pop   bx         ;Root directory entries
   xor   di, di         ;Point at directory {1C}
.20:   mov   si, file_name      ;Name of file we want
   xor   ecx, ecx
   mov   cl, 11
   a32 rep cmpsb         ;Found the file?
   je   found         ;Yes
   add   cl, 21         ;Offset to next directory entry
   add   edi, ecx      ;Advance to next entry
   dec   bx         ;Loop through all entries
   jnz   .20

   ;Couldn't find file in directory
boot_error:
disk_error:   
   mov   ax, 0xE07      ;{3}
   int   10h
   jmp short $

;>> ecx = 00000000
;> es = 800
;> es:edi = Directory entry of file
;> ebp = LBN of cluster 2
;> eax = 0000????

found:   push   word [es:edi+0xF]   ;Starting cluster of file
   mov   di, [boot+BB_fat]   ;Size of FAT (in sectors)
   mov   ax, [boot+BB_res]   ;LBN of FAT
   call   read_sectors

   mov   bx, 0x4000
   mov   es, bx         ;es = 0x4000
   mov   edi, 0x100000-0x40000   ;{1D}{4B} One megabyte minus ES base
.10:

;>> ecx = 0000????
;> [sp] = Next cluster of file
;> esi = 0000????
;>> edx = 0000????
;> es:edi = Destination address
;> ebp = LBN of cluster 2
;> ds = 0

   xor   eax, eax
   pop   si         ;Next cluster of file
   mov   bx, si
   cmp   si, 0xFF8      ;Valid cluster?
   jae   eof         ;No: assume end of file
               ;Yes: (c-bit set)
   rcr   bx, 1         ;bx = 0x8000 + cluster/2
   mov   bx, [bx+si]      ;Get word containing FAT entry
   jnc   .11         ;Entry is low 12 bits
   shr   bx, 4         ;Entry was high 12 bits
.11:   and   bh, 0xF         ;Mask to just 12 bits
   push   bx         ;Save cluster after next
   push   di         ;Save destination address {7}
   mov   al, [boot+BB_clu]   ;Size of each cluster
   mov   di, ax         ; (in sectors)
   dec   si
   dec   si
   mul   esi         ;Times cluster number minus 2
   add   eax, ebp      ;Plus LBN of cluster 2   
   call   read_sectors      ;Read that cluster

;> ecx = 0000????
;>> edx = 0000????
;> di = Clustersize in sectors
;> esi = 0
;>> ebp = LBN of cluster 2
;> [sp] = Bottom 16-bits of destination address {7}
;>> [sp+2] = Following cluster
;> ds = 0
;> es = 4000

   mov   cx, di         ;Cluster size in sectors
   xchg   ch, cl         ;Cluster size in words
   pop   di         ;Restore destination address {7}
   es a32 rep movsw
   jmp short .10         ;Loop until end of file

;> eax = 0
;> edx = 0000????
;> bx = 0FF?

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 7:15 pm
by AlanO
eof:
   mov   dx, 0x9C00
   mov   es, dx         ;es = 9C00
   xor   di, di         ;{1E} Address of page tables WRT es
   mov   dh, 4096/256      ;edx = 4096
.10:   mov   cx, 1024
   mov   al, 7
.20:   stosd
   add   eax, edx
   int   8         ;{8}
   loop   .20
   shr   eax, 2         ;{4C} (first time only) 4Mb / 4 = 1Mb
   neg   bl         ;Done just one page?
   jns   .10         ;Yes: do one more

   cli            ;{6}

   mov   eax, 0x9C007      ;First page tbl pointer in page dir
   stosd            ;{1H}
   mov   ax, (1024-3)*2
   xchg   ax, cx
   rep stosw
   mov   ax, 0xD007      ;0FF800000 page tbl pointer
   stosd            ;{1F}
   mov   ah, 0xE0      ;Page directory self pointer
   stosd            ;{1G}
   mov   al, 0
   mov   CR3, eax      ;Set up page directory
   mov   eax, CR0      ;Turn on paging and protected mode
   or   eax, 0x80000001
   mov   CR0, eax
   mov   cl, flat_data      ;Setup ds and es
   push   cx         ;{5}
   pop   ds
   mov   es, cx
   jmp dword 8:0xFF800000      ;Go
   
read_sectors:
; Input:
;   EAX = LBN
;   DI = sector count
;   ES = segment
; Output:
;   EBX high half cleared
;   DL = drive #
;   EDX high half cleared
;   ESI = 0
; Clobbered:
;   BX, CX, DH

   push   eax
   push   di
   push   es

.10:   push   eax      ;LBN

   cdq         ;edx = 0
   movzx   ebx, byte [boot+BB_sec]
   div   ebx      ;EAX=track ;EDX=sector-1
   mov   cx, dx      ;CL=sector-1 ;CH=0
   sub   bl, dl      ;BX = max transfer before end of track
   cmp   di, bx      ;Do we want more than that?
   ja   .20      ;Yes, do just this much now
   mov   bx, di      ;No, do it all now
.20:   mov   esi, ebx   ;Save count for this transfer.

   inc   cx      ;CL=Sector number
   xor   dx, dx
   mov   bl, [boot+BB_head]
   div   ebx      ;EAX=cylinder ;EDX=head

   mov   dh, dl      ;Head
   mov   dl, [boot]   ;Drive
   xchg   ch, al      ;CH=Low 8 bits of cylinder number; AL=0
   shr   ax, 2      ;AL[6:7]=High two bits of cylinder
   or   cl, al      ;CX = Cylinder and sector

   mov   ax, si      ;Sector count
   mov   ah, 2      ;Read
   xor   bx, bx
   push   ax
   int   13h
   pop   ax
   jnc   .30

   int   13h      ;If at second you don't succeed, give up
   jc near   disk_error

.30:   pop   eax
   add   eax, esi   ;Advance LBN

   push   si
   shl   si, 5
   mov   bx, es
   add   bx, si      ;Advance segment
   mov   es, bx
   pop   si

   sub   di, si
   ja   .10

   pop   es
   pop   di
   pop   eax
   xor   si, si
   ret   

file_name db 'KERNEL BIN'

gdt   start_gdt      ;{9}

flat_code   desc   0, 0xFFBFF, D_CODE+D_READ+D_BIG+D_BIG_LIM

flat_data   desc   0, 0xFFFFF, D_DATA+D_WRITE+D_BIG+D_BIG_LIM

   end_gdt

   resb 0x1FE+$$-$
   db   0x55, 0xAA      ;Standard end of boot sector
;_________________________________________________________________________

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 7:16 pm
by AlanO
okay sorry about having to paste all of that, but i'm really lost, i think its because i am pmode, so should i switch out? and then if i wanna do that, am i able to do that in a C call to an asm funciton? or just using inline asm with GCC?

hmnmm?? lol

thank you for all your help so far!

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 7:36 pm
by dronkit
i'll take a look at your code in a minute...

but i'm sure you know a little about what you're doing ;)

you have to know if you're working in pmode, rmode, or unreal mode.

Second thing, 16/32 bits or mixed. your stack should be set as either one or the other, depending on your code.

but you can't call BIOS directly from pmode 32 bits. that's for sure ;)

when you issue your int $0x16 (thus, calling bios) you have to be in real mode or unreal mode, running 16 bit code (the bios has 16 bits opcodes)

if you want to run always in pmode you'll have to code your own console drivers (for screen and keyboard). Thus, writing bytes at $0xB000 (the 80x25 video buffer) and reading from port $0x60 (the keyboard)

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 7:59 pm
by AlanO
heh well that bootsector isn't mine and i'm trying to just do a kernel then worry about my own bootsector. I do have a really lame one i wrote, but it barely loads my own kernel half of the time, but anyways, i have no idea lol

Re:Keyboard handler problem

Posted: Mon Sep 23, 2002 8:14 pm
by dronkit
well... you could use grub or something like that, or the one used in v2 or some of the examples here.. or take a look at this ;)
http://www.mega-tokyo.com/forum/index.p ... eadid=1542

(you might also like to read the intel 386 programming manual if you are going to do some asm)

Re:Keyboard handler problem

Posted: Tue Sep 24, 2002 11:07 am
by Whatever5k
I suggest to use GRUB instead, too. There are so many people having trouble with their own bootloader, although they understood the basic things of getting into PMode - so, don't lose your time with that, take GRUB - you'll have to set up a GDT and IDT in GRUB, too; so it's also quite interesting...