Page 1 of 2

Reading the kernel from floppy in RM

Posted: Fri Apr 06, 2007 2:25 am
by XCHG
In the first boot loader that I wrote, I was reading 8KB from the floppy starting from Track#0 Sector #2 and up to 17 tracks. This made it a total number of 17*512=8704 bytes. Now that the size of my kernel has passed the 8 KB limit, I added some more code to my boot loader to read the second track of the floppy drive to make it a total of (17+18)*512 = 17920 bytes. The first attempt reads 17 Sectors from the first track of the disk and the second attempt reads 18 sectors from the second track but the problem is that the second attempt doesn't seem to work because every byte after Byte#8704 seems to be trashed when I attempt to address it in my kernel. I simplified the code of the second read attempt and put it here. I'd appreciate it if somebody could tell me what I might be doing wrong.

Oh also about where the second track should be read: My kernel starts at the 1MB mark so the segment address of the destination should be 0xFFFF and the offset should be 0x0010. After the first read attempt, the offset should be increased (17*512) = 8704 bytes. Therefore, the ES:BX will contain 0xFFFF:(0x0010+(17*512)) or 0xFFFF:0x2210. I thought I point this out to avoid confusion.

Code: Select all

  MOV     AX , 0xFFFF       ; The segment address of the destination
  MOV     ES , AX           ; ES = The segment address
  .ReadAttempt2:            ; Read the second Track
    XOR     AH , AH         ; Function #0, Reset Drive
    XOR     DL , DL         ; Drive #0
    INT     0x13            ; Issue the Interrupt
    JC      .ReadAttempt2   ; Keep resetting the drive upon failure
    MOV     BX , 8720       ; 17*512 = 8704, 8704+16 = 8720
    MOV     AH , 0x02       ; Function #2, Read Sectors
    MOV     AL , 18         ; Read 18 sectors
    MOV     CH , 0x01       ; From the second track (0..1)=2
    MOV     CL , 0x01       ; Starting from Sector #1
    XOR     DX , DX         ; Drive = A, Head = 0
    INT     0x13            ; Issue the Interrupt
    JC      .ReadAttempt2   ; Keep reading if an error has occurred

Posted: Fri Apr 06, 2007 2:57 am
by ~
Are you using a FAT12 bootloader? If not, why? It would do your life much easier.

For your current issue, it would be better if you had a function to read sector-by-sector because it's the way I do and seems to be the easiest. In that case you could make it a subroutine that converts a LBA sector number into a CHS and then reads the kernel where it should. So in that loop you would just need to update your memory pointer in 512-byte increments and also your LBA number.

Other thing I see is that I don't reset the floppy that much, I just try to read it some 2 or 3 times and then give up.

Posted: Fri Apr 06, 2007 3:50 am
by Combuster
Are you aware of the fact that 0010:0000 != 0000:0010 :?

Posted: Fri Apr 06, 2007 5:36 am
by ~
Try the following boot record. It can be compiled with NASM and is fully functional. Currently it loads the kernel at 0x100000, and must be called KERNEL.BIN in the floppy root directory. It's based in a ZIP file called bootf02.zip.

It enables Unreal Mode (to forget greatly about segment issues and being able to address the full 4GB from RM) and Protected Mode, enables A20 address line, only a code and data selectors, and no paging.

Since it's FAT12-compliant, you just have to copy this MBR to a standard 1.4Mb floppy and copy the kernel file. You must name it "KERNEL.BIN" or "kernel.bin". If you want to use another 8.3 name, you will have to change the 11-byte kernelFile variable.

To change the address where the kernel is copied and control is passed on, you must change the value of the __MyKernelPlainEntry__ constant.

Since the original boot tutorial was free to use, the following can be used freely as well.

Code: Select all

org 7C00h

__MyKernelPlainEntry__ equ 0x100000


_jmp: jmp short start
_nop: nop
_OEMid              db    "        "
_bytesPerSect       dw         0200h
_sectsPerClus       db          001h
_resrvedSects       dw         0001h
_numOfFATs          db          002h
_numRootDirEntries  dw         00E0h
_numSectors         dw         0B40h
_mediaType          db          0F0h
_numFATsectors      dw         0009h
_sectorsPerTrack    dw         0012h
_numHeads           dw         0002h
_numHiddenSects     dd     00000000h
_numSectorsHuge     dd     00000000h
_driveNumber        db           00h
_reserved           db           00h
_signature          db           29h
_volumeID           db        "    "
_volumeLabel        db "           "
_FSType             db    "FAT12   "


;INIT: 448 free bytes:
;INIT: 448 free bytes:
;INIT: 448 free bytes:
 ;>   cs = 0
 ;>>  dl = drive we were booted from
 ;INIT: enable protected mode (time 1 out of 2) to load GDT
 ;INIT: enable protected mode (time 1 out of 2) to load GDT
 ;INIT: enable protected mode (time 1 out of 2) to load GDT

  start:  cli                             ;{0}
          lgdt    [cs:GDT]                ;Load GDT.
            mov     ecx, CR0              ;Switch to protected mode
            inc     cx
            mov     CR0, ecx          ;{5}
 ;END:  enable protected mode (time 1 out of 2) to load GDT
 ;END:  enable protected mode (time 1 out of 2) to load GDT
 ;END:  enable protected mode (time 1 out of 2) to load GDT


;;INIT: enable A20
;;INIT: enable A20
;;INIT: enable A20
  ;registers modified in this INIT--END section:
   ;AX (EAX)
     ;registers wich values to reuse in the next INIT--END:
      ;AH (will be 0)

  .5:     in      al, 0x64              ;Enable A20 {4A}.
          test    al, 2     ;see if bit 1 returned from port
                            ;0x64 is 1, which means that
                            ;controller is not ready
          jnz     .5    ;repeat until bit 1 from 0x64 is cleared to 0,
                        ;indicating the keyboard controller is ready

        mov     al, 0xD1    ;*WRITE OUTPUT PORT* command
          out     0x64, al    ;send it

.6:     in      al, 0x64    ;read port 0x64
        and     ax, byte 2   ;see if bit 1 is set to 0
                             ;NOTE: it will leave AH set to 0 at once
                             ;      to be used in the next INIT--END block.
          jnz     .6           ;repeat until keyboard controller is ready
                               ;(bit 1 cleared to 0)


        mov     al, 0xDF    ;configure keyb. controller bit-set
            out     0x60, al   ;send it to data port, to enable A20
;;END:  enable A20
;;END:  enable A20
;;END:  enable A20




 ;;INIT: register/memory parameters configuration
 ;;INIT: register/memory parameters configuration
 ;;INIT: register/memory parameters configuration
  ;registers to modify in this INIT--END section:
   ;AX (EAX) 0
   ;DS 0
   ;ES 0x800
   ;SS 0
   ;SP 0x800

     ;registers with values to reuse in the next INIT--END block:
      ;apparently ALL of the above

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

        mov     al,Data32
        mov     ds, ax                  ;{2} Extend limit for ds.
        mov     es, ax                  ;Extend limit for es.

        dec     cx                      ;Switch back to and into (Un)Real mode.
	mov	CR0, ecx		;{5}


  ;Here we are in (Un)Real Mode:
  ;Here we are in (Un)Real Mode:
  ;Here we are in (Un)Real Mode:
        mov     [_jmp], dl         ;Save drive number we came from.
        mov     sp, 0x800              ;Configure stack end to 0x800

        xor     eax, eax                ;Segment. 32 bits cleared to 0
        mov     ds, ax                  ;DS (Data Segment) cleared to 0
        mov     ss, ax                  ;SS (Stack Segment) cleared to 0
        mov     es, sp                  ;Read directory at 800:0 {1C}. ES
                                        ;(Extra Segment) 0x800.
 ;;END:  register/memory parameters configuration
 ;;END:  register/memory parameters configuration
 ;;END:  register/memory parameters configuration




 ;;INIT: configure floppy information
 ;;INIT: configure floppy information
 ;;INIT: configure floppy information
  ;>   eax = 00000000

  ;We keep in Unreal Mode from the previous INIT--END:
  ;We keep in Unreal Mode from the previous INIT--END:
  ;We keep in Unreal Mode from the previous INIT--END:
        mov     al, [_numOfFATs]      ;Number of FATs
        mul     byte [_numFATsectors] ;Times size of FAT |(in sectors?)
        add     ax, [_resrvedSects]   ;Plus Sectors before first FAT
                 ;(_numOfFATs*_numFATsectors)+_resrvedSects
					;eax = LBN of Root directory

        movzx   edi,word [_numRootDirEntries] ;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    ;call forward
 ;;END:  configure floppy information
 ;;END:  configure floppy information
 ;;END:  configure floppy information



 ;;INIT: look for 8.3 name in the floppy root directory
 ;;INIT: look for 8.3 name in the floppy root directory
 ;;INIT: look for 8.3 name in the floppy root directory
  ;>  eax  = LBN of root directory
  ;>  edi  = length of root directory in sectors
  ;>  [sp] = length of root directory in entries
  ;>  esi  = 00000000

  ;We keep here in Unreal Mode from the 2 previous INIT--END blocks:
  ;We keep here in Unreal Mode from the 2 previous INIT--END blocks:
  ;We keep here in Unreal Mode from the 2 previous INIT--END blocks:
	lea	ebp, [eax+edi]		;ebp = LBN of cluster 2

        pop     bx                      ;Root directory entries.

        xor     di, di               ;Point at directory {1C}
  .20:  mov     si, kernelFile       ;Name of file we want.

	xor	ecx, ecx
        mov     cl, 11       ;bytes in string "KERNEL  BIN"
        a32 rep cmpsb                   ;Found the file?.
                                        ;we use the 11 in CL
	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          ;Ring the bell on error...
        jmp short $     ;end with infinite loop
 ;;END:  look for 8.3 name in the floppy root directory
 ;;END:  look for 8.3 name in the floppy root directory
 ;;END:  look for 8.3 name in the floppy root directory



 ;;INIT: read file according what the previous INIT--END found
 ;;INIT: read file according what the previous INIT--END found
 ;;INIT: read file according what the previous INIT--END found
  ;>> 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, [_numFATsectors] ;Size of FAT (in sectors)
          mov     ax, [_resrvedSects]  ;LBN of FAT
            call    read_sectors    ;call forward

	mov	bx, 0x4000
	mov	es, bx			;es = 0x4000
	mov	edi, __MyKernelPlainEntry__-0x40000	;{1D}{4B} One megabyte minus ES base
 ;;END:  read file according what the previous INIT--END found
 ;;END:  read file according what the previous INIT--END found
 ;;END:  read file according what the previous INIT--END found




 ;;INIT: final processes and control transfer to kernel entry point
 ;;INIT: final processes and control transfer to kernel entry point
 ;;INIT: final processes and control transfer to kernel entry point
  .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, [_sectsPerClus]     ;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?

  eof:
.20:
	int	8			;{8}
	loop	.20

	cli				;{6}

	mov	eax, CR0		;Turn on protected mode
	or	eax, 0x00000001
	mov	CR0, eax
        mov     cl, Data32              ;Setup ds and es
	push	cx			;{5}
	pop	ds
	mov	es, cx
     a32   jmp dword Code32:__MyKernelPlainEntry__   ;Go

 ;;END:  final processes and control transfer to kernel entry point
 ;;END:  final processes and control transfer to kernel entry point
 ;;END:  final processes and control transfer to kernel entry point




 ;;INIT: read_sectors
 ;;INIT: read_sectors
 ;;INIT: read_sectors
  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 [_sectorsPerTrack]
          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, [_numHeads]
          div     ebx             ;EAX=cylinder ;EDX=head

          mov     dh, dl          ;Head
          mov     dl, [_jmp]  ;Drive number
          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 
 ;;END:  read_sectors
 ;;END:  read_sectors
 ;;END:  read_sectors


 kernelFile db 'KERNEL  BIN'


 ;INIT: GDT
 ;INIT: GDT
 ;INIT: GDT
   GDT:
   _SELNulo equ 0   ;WARNING: this sector, besides being the GDT pointer,
      GDT_size:     ;         is the NULL selector.
        dw GDTsize
      GDT_actualptr:
        dd GDT
       dw 0x0000

   Code32 equ 8
     dw 0FFFFh       ; bits 0-15 length
     dw 00000h       ; bits 0-15 base addr
     db 0            ; bits 16-23 base addr
     db 10011010b    ; bits P,DPL,DT & type
     db 11001111b    ; bits G,D & bits 16-19 length
     db 0            ; bits 24-31 base addr

   Data32 equ 16
     dw 0FFFFh       ; bits 0-15 length
     dw 00000h       ; bits 0-15 base addr
     db 0            ; bits 16-23 base addr
     db 10010010b    ; bits P,DPL,DT & type
     db 11001111b    ; bits G,D & bits 16-19 length
     db 0            ; bits 24-31 base addr
   GDT_end:

   GDTsize equ (GDT_end-GDT)-1
 ;END:  GDT
 ;END:  GDT
 ;END:  GDT

 times (510-($-$$)) db 0

;END:  448 free bytes
;END:  448 free bytes
;END:  448 free bytes


dw 0xAA55

Posted: Fri Apr 06, 2007 11:02 am
by Dex
Maybe you should just switch heads :wink:
Eg: you should read the first track, than you need to change the head to 01 and repeat the reading the same track. as i think your reading garbage. As there two sides .

Posted: Fri Apr 06, 2007 11:57 am
by ~
Dex wrote:Maybe you should just switch heads :wink:
Eg: you should read the first track, than you need to change the head to 01 and repeat the reading the same track. as i think your reading garbage. As there two sides .
But maybe that would be a "nonstandard" way of addressing CHS sectors, not used by FAT filesystems and at least I don't know of any CHS conversion method which uses that sort of sequence.

And, as far as I know, calculating such numbers is not as straightforward as the CHS methods normally used by FAT filesystems and the like.

Or better, I think I'm wrong, so maybe take a look at the following file, which shows the CHS sequence normally used for FAT, etc., and that has just been suggested by others:

http://didactos.blogsyte.com/disks/lba2chs.html (360Kb)

Posted: Sun Apr 08, 2007 1:08 am
by XCHG
Okay I think the boot loader that I have written was the first part of my Operating System and my first attempt to write a boot loader, so it pretty much blows. I guess using a FAT12 boot loader is a way to go. And also about heads, I had no idea I had to change the head for each track. So let me get this straight: you read one track (18 sectors on 1.44”) and then to be able to read the next track, you have to move to Head#1 and then when you are done there, you have to come back to Head#0. Is that right?


Combuster,
I guess I didn’t explain my point correctly. See my kernel is at the 1MB mark. Setting the segment to 0xFFFF and the offset to 0x0010 will get us to 1MB. (0xFFFF << 0x04) + 0x0010.


Thank you guys so much. Appreciations.

Posted: Sun Apr 08, 2007 6:51 am
by mystran
XCHG wrote:Okay I think the boot loader that I have written was the first part of my Operating System and my first attempt to write a boot loader, so it pretty much blows. I guess using a FAT12 boot loader is a way to go. And also about heads, I had no idea I had to change the head for each track. So let me get this straight: you read one track (18 sectors on 1.44”) and then to be able to read the next track, you have to move to Head#1 and then when you are done there, you have to come back to Head#0. Is that right?
There is nothing wrong with having a bootloader without a filesystem, for the purpose of loading a kernel off floppy. For obvious reasons that won't work as such if you want a filesystem on the same disk (say, harddisk) but the lack of filesystem is almost certainly not the problem.

If you've formatted the disk as 1.44MB, and just use a random utility to write the disk, you almost certain need to first read the first track (0) with head 0, then with head 1, then second track (1) with head 0, then with head 1, and so on.

(Technically there's two tracks per cylinder, one for head0 and one for head1, but...)

Posted: Thu Apr 12, 2007 1:35 am
by XCHG
I'm sorry for piggybacking on this post but I made my first FAT12 compliant boot loader and then I had problems loading the kernel in Real Mode because if the size of the file reaches 64K, the RM addressing mode will not be able to handle that even when the KBD A#20 pin is opened. I then thought of using Unreal Mode. So what I am doing is that I am loading one sector from the kernel's file on disk at a time to the physical address 0x000FFE00 which is 512 bytes below the 1MB mark, where my kernel will be placed. I then used MOVSD to move the 512 bytes of the sector that is read and then I place it at the 1MB mark. The destination will then be incremented 512 bytes in each iteration. But the problem is that as soon as I use a JMP instruction to jump to kernel's entry, I get this error from Bochs:

Code: Select all

00005842101e[CPU0 ] exception(): 3rd (13) exception with no resolution, shutdown
 status is 00h, resetting
And this is how I am enabling Unreal Mode:

Code: Select all

    PUSH    DS               ; Preserve the data segment
    PUSH    ES               ; Preserve the extra segment
    PUSH    FS               ; Preserve FS
    PUSH    GS               ; Preserve GS
    LGDT    [GDTR]           ; Load the Global Descriptor Table
    MOV     EAX , CR0        ; Enable Protected Mode, Step 1
    OR      EAX , 0x00000001 ; Enable Protected Mode, Step 2
    MOV     CR0 , EAX        ; Enable Protected Mode, Step 3
    JMP     $+2              ; Flush CS:EIP
    MOV     AX , DATASEL     ; AX = The Data Segment Selector
    MOV     ES , AX          ; ES = DS
    MOV     DS , AX          ; DS = DS
    MOV     GS , AX          ; GS = DS
    MOV     FS , AX          ; FS = DS
    MOV     EAX , CR0        ; Go to Unreal Mode, Step 1
    AND     EAX , 0xFFFFFFFE ; Go to Unreal Mode, Step 2
    MOV     CR0 , EAX        ; Go to Unreal Mode, Step 3
    JMP     $+2              ; Flush CS:EIP
    POP     GS               ; Restore GS
    POP     FS               ; Restore FS
    POP     ES               ; Restore the extra segment
    POP     DS               ; Restore the data segment
I can also post the code that I have written for reading the kernel from the floppy, if you guys think it is needed. It'd be great if someone could help me with this. Thanks in advance.

Posted: Thu Apr 12, 2007 1:53 am
by Combuster
Shall we start with finding out the faulting instruction?

Posted: Thu Apr 12, 2007 3:33 am
by XCHG
The exception is caused when I jump to my kernel's entry.

Code: Select all

    CLI                             ; Disable Traps
    MOV     EAX , CR0               ; Enable Protected Mode, Step 1
    OR      EAX , 0x0000001         ; Enable Protected Mode, Step 2
    MOV     CR0 , EAX               ; Enable Protected Mode, Step 3
    JMP     CODESEL:.FlushCSEIP     ; Flush Real Mode CS:EIP
    [BITS 32]                       ; All 32-bit operands and code
    .FlushCSEIP:                    ; CS:EIP is flushed
      MOV     EAX , DATASEL         ; EAX = Data Segment Selector
      MOV     ES , EAX              ; ES = DS
      MOV     DS , EAX              ; DS = DS
      MOV     FS , EAX              ; FS = DS
      MOV     GS , EAX              ; GS = DS
      MOV     SS , EAX              ; SS = DS
      MOV     SP , 0x0000FFFF       ; The Stack Pointer at 0xFFFF
      JMP     CODESEL:KERNELENTRY   ; *** THIS CAUSES THE EXCEPTION ***

Posted: Thu Apr 12, 2007 4:20 am
by XCHG
Alright I think there should be a problem with transferring the bytes from 0xFFE0:0x0000 to the physical address of 0x00100000 (1MB). I moved one HLT instruction and 3 NOPs to the 1MB mark, where my kernel starts and then jumped to that location but no exceptions were fired.

Code: Select all

MOV     DWORD PTR [MEGABYTE(1)] , 0x909090F4
This means that I am reading trash from the floppy. I am assuming that the kernel file is the first file copied to the FAT12 floppy. This way it will be located at the absolute address of 0x4200 in the floppy. Here is how I am reading the kernel from floppy:

Code: Select all

; ——————————————————————————————————————————————
JMP     __Start
PreviousDestination     DD        MEGABYTE(1)     ; Start writing to 1MB mark and forth
; ——————————————————————————————————————————————
__Start:
MOV     AX , 0xFFE0                               ; AX = 0xFFE0, Destination's segment
MOV     ES , AX                                   ; ES = 0xFFE0
XOR     BX , BX                                   ; ES:BX = 0xFFE0:0x0000
MOV     DH , 0x01                                 ; [HeadNumber] = 0x01
MOV     DL , BYTE PTR [BootDrive]                 ; [RootDrive] = 0x00 (A)
MOV     CH , 0x00                                 ; [CylinderNumber] = 0x00
MOV     CL , 0x10                                 ; [SectorNumber] = 16
; ——————————————————————————————————————————————
.ReadKernel:                                      ; Start reading the kernel from LSN(34)
  CALL    __ResetFloppy                           ; Reset the floppy drive
  MOV     AH , 0x02                               ; Read Sector Function
  MOV     AL , 0x01                               ; Read one sector only (512 Bytes)
  INT     0x13                                    ; Attempt to read the sector now
  JC      .ReadKernel                             ; Keep resetting and reading upon failure
  INC     CL                                      ; SectorNumber = SectorNumber + 1 (Next Sector)
  .AdjustCHS:                                     ; Adjust the CHS address to reflect the progress
    CMP     CL , 0x12                             ; See if we have yet reached Sector #18
    JBE     .NoNeedForCHSAdjustment               ; Jump to ... if Sector <= 18
    MOV     CL , 0x01                             ; Start from Sector 1 again
    XOR     DH , 0x01                             ; Reverse the head (1->0) and (0->1)
    JNZ     .NoNeedForCHSAdjustment               ; If the Head is 0, Cylinder should be incremented
    INC     CH                                    ; Increment the Cylinder
  .NoNeedForCHSAdjustment:                        ; Here is no need to adjust the CHS
    MOV     AX , 0x0E23                           ; Print # to the screen for progression
    INT     0x10                                  ; Print # after reading each sector
    MOV     EAX , ECX                             ; Keep the CL and CH in a safe place
    MOV     ESI , 0x00FFE00                       ; *ESI = Where the sector is read
    MOV     EDI , DWORD PTR [PreviousDestination] ; EDI = Where the sector should be copied to
    MOV     ECX , 0x00000080                      ; 128 DWORDs (128*4=512 Bytes)
    CLD                                           ; Move forward
    REP     MOVSD                                 ; Read from ES:BX and copy to destination
    MOV     DWORD PTR [PreviousDestination] , EDI ; Put the new destination into EDI
    MOV     ECX , EAX                             ; Restore ECX
    DEC     WORD PTR [FileSectorCount]            ; Decrement the number of sectors to be read
    JNZ      .ReadKernel                          ; Keep reading if FileSectorCount > 0
; ——————————————————————————————————————————————
So basically I read one sector from the floppy to 0xFFE0:0x0000 and then transfer it to the 1MB mark and forth. There must be something wrong with this transfer that I can not find out.

Posted: Thu Apr 12, 2007 6:52 am
by os64dev
So basically I read one sector from the floppy to 0xFFE0:0x0000 and then transfer it to the 1MB mark and forth. There must be something wrong with this transfer that I can not find out.
So your reading a sector into a read only memory area, not the smartest thing to do ;-) Keep your memory usage below the 640 KiB when in real mode. Try 0x9000:0000 maybe that should work.

Posted: Thu Apr 12, 2007 7:27 am
by ~
XCHG wrote:I'm sorry for piggybacking on this post but I made my first FAT12 compliant boot loader and then I had problems loading the kernel in Real Mode because if the size of the file reaches 64K, the RM addressing mode will not be able to handle that even when the KBD A#20 pin is opened. I then thought of using Unreal Mode. So what I am doing is that I am loading one sector from the kernel's file on disk at a time to the physical address 0x000FFE00 which is 512 bytes below the 1MB mark, where my kernel will be placed. I then used MOVSD to move the 512 bytes of the sector that is read and then I place it at the 1MB mark. The destination will then be incremented 512 bytes in each iteration. But the problem is that as soon as I use a JMP instruction to jump to kernel's entry, I get this error from Bochs:
Why don't use Unreal mode to load your kernel? For the most part you could stop worrying segment registers, and you could just set them to a value of 0 to make it far easier.

You can even use 32-bit registers and offsets freely to copy your kernel anywhere you want, and no matter its size...

What about if your kernel gets bigger abruptly?

Posted: Thu Apr 12, 2007 11:38 am
by XCHG
~:

I am in Unreal Mode when I am reading the kernel from the disk. The problem is that INT 0x13 stills needs segments to be specified and perhaps if you specify ES as 0x0000, then the physical address of where the sectors will be read will be equal to BX.