Confused on FAT (table design)

Question about which tools to use, bugs, the best way to implement a function, etc should go here. Don't forget to see if your question is answered in the wiki first! When in doubt post here.
Post Reply
User avatar
BASICFreak
Member
Member
Posts: 284
Joined: Fri Jan 16, 2009 8:34 pm
Location: Louisiana, USA

Confused on FAT (table design)

Post by BASICFreak »

ok, I started over on my OS again this time trying everything from scratch.
So far my floppy code is:

Code: Select all

;****************************************
;	BIOS Entry Point
;****************************************
use16
org 0x7C00

jmp startbs
;****************************************
;	OEM Parameter Block
;****************************************
OSID			db	"HooverOS"
BytesPerSector		dw	0200h
SectorsPerCluster	db	01h
ReservedSectors		dw	0001h
NumberofFATs		db	02h
RootEntries		dw	00E0h
TotalSectors		dw	0B40h
MediaType		db	0F0h
SectorsPerFAT		dw	0009h
SectorsPerTrack		dw	0012h
HeadsPerCylinder	dw	0002h
HiddenSectors		dd	00000000h
TotalSectorsBig		dd	00000000h
DriveNumber		db	00h
ReservedUNUSED		db	00h
BootSigniture		db	29h
SerialNumber		dd	69696969h
VolumeLable		db	"Hoover OS 1"
FileSystem		db	"FAT12   "

;****************************************
;	Functions
;****************************************
print:
  lodsb
  or	al,	al
  jz	done
  mov	ah,	0Eh
  int	10h
  jmp	print
  
  
done:
  ret

;****************************************
;	Boot Sector Entry Point
;****************************************
startbs:
  xor	ax,	ax
  mov	ds,	ax
  mov	es,	ax
  
  mov	si,	bootmsg
  call	print
  
  cli
  hlt
;****************************************
;	Variables
;****************************************
bootmsg			db	"Booting OS...", 10, 0

;****************************************
;	Pad file to 510 bytes with 0
;	Boot Signiture 511 0x55 512 0xAA
;****************************************
times 510 - ($-$$) db 0
dw 0xAA55

;****************************************
;	FAT TABLE 1
;****************************************
db 0xf0
db 0xff
db 0xff
times 5120 - ($-$$) db 0x00

;****************************************
;	FAT TABLE 2
;****************************************
db 0xf0
db 0xff
db 0xff
times 9728 - ($-$$) db 0x00

;****************************************
;	Root Directory
;****************************************
db "HOOVER OS 1"
times 10 db 0
db 0xf3
db 0x85
db 0x97
db 0x41

;****************************************
;	Make into Floppydisk Image
;	Pad to 1440KB with 0
;****************************************
times 1474560 - ($-$$) db 0
I looked at a FAT formatted floppy from windows in a hex editor to TRY and figure out how the table is designed, but now that I got the data where windows put it I'm still showing that the disk is "not formatted"

Please can someone point me in the right direction...
User avatar
BASICFreak
Member
Member
Posts: 284
Joined: Fri Jan 16, 2009 8:34 pm
Location: Louisiana, USA

Re: Confused on FAT (table design)

Post by BASICFreak »

Well I found my issue...
the OEM Parameter Block must start at byte 3, but a jump command is only 2 bytes so all I had to do was db another 0 before the OEM Block

code for anyone who may want it...:

Code: Select all

;****************************************
;	BIOS Entry Point
;****************************************
use16
org 0x7C00

jmp startbs
;****************************************
;	Fill in space befor OEM Block
;****************************************
times 3 - ($-$$) db 0

;****************************************
;	OEM Parameter Block
;****************************************
OSID			db	"HooverOS"
BytesPerSector		dw	0200h
SectorsPerCluster	db	01h
ReservedSectors		dw	0001h
NumberofFATs		db	02h
RootEntries		dw	00E0h
TotalSectors		dw	0B40h
MediaType		db	0F0h
SectorsPerFAT		dw	0009h
SectorsPerTrack		dw	0012h
HeadsPerCylinder	dw	0002h
HiddenSectors		dd	00000000h
TotalSectorsBig		dd	00000000h
DriveNumber		db	00h
ReservedUNUSED		db	00h
BootSigniture		db	29h
SerialNumber		dd	9ce4e305h
VolumeLable		db	"Hoover OS 1"
FileSystem		db	"FAT12   "

;****************************************
;	Functions
;****************************************
print:
  lodsb
  or	al,	al
  jz	done
  mov	ah,	0Eh
  int	10h
  jmp	print
  
  
done:
  ret

;****************************************
;	Boot Sector Entry Point
;****************************************
startbs:
  xor	ax,	ax
  mov	ds,	ax
  mov	es,	ax
  
  mov	si,	bootmsg
  call	print
  
  cli
  hlt
;****************************************
;	Variables
;****************************************
bootmsg			db	"Booting OS...", 0

;****************************************
;	Pad file to 510 bytes with 0
;	Boot Signiture 511 0x55 512 0xAA
;****************************************
times 510 - ($-$$) db 0
dw 0xAA55

;****************************************
;	FAT TABLE 1
;****************************************
db 0xf0
db 0xff
db 0xff
times 5120 - ($-$$) db 0x00

;****************************************
;	FAT TABLE 2
;****************************************
db 0xf0
db 0xff
db 0xff
times 9728 - ($-$$) db 0x00

;****************************************
;	Root Directory
;****************************************
db "HOOVER OS 1"
times 11 db 0
db 0x96
db 0x88
db 0x97
db 0x41
times 16896 - ($-$$) db 0x00
;****************************************
;	Make into Floppydisk Image
;	Pad to 1439.5KB with 0xf6
;	Pad to 1440KB with 0x00
;****************************************
times 1474048 - ($-$$) db 0xf6
times 1474560 - ($-$$) db 0x00
egos
Member
Member
Posts: 612
Joined: Fri Nov 16, 2007 1:59 pm

Re: Confused on FAT (table design)

Post by egos »

FAT Spec. says that this byte must be 0x90 (nop) when short jump was used.
If you have seen bad English in my words, tell me what's wrong, please.
User avatar
BASICFreak
Member
Member
Posts: 284
Joined: Fri Jan 16, 2009 8:34 pm
Location: Louisiana, USA

Re: Confused on FAT (table design)

Post by BASICFreak »

egos wrote:FAT Spec. says that this byte must be 0x90 (nop) when short jump was used.
Yes, and I have changed it but after adding my FAT12 driver to the bootsector it ended up being a long jump which is 3 bytes.

Can someone explain to me how this changed on me?!? It is within the 64KiB area (within 512 bytes)
jmp short startbs
nop
errors at jmp short says it is not a short jump

I can live with it as it does work but my curiosity just gets the best of me

Honestly this is the first time I actually wrote anything in ASM, all my ASM code before was just copied and pasted...
BOS Source Thanks to GitHub
BOS Expanded Commentary
Both under active development!
Sortie wrote:
  • Don't play the role of an operating systems developer, be one.
  • Be truly afraid of undefined [behavior].
  • Your operating system should be itself, not fight what it is.
Antti
Member
Member
Posts: 923
Joined: Thu Jul 05, 2012 5:12 am
Location: Finland

Re: Confused on FAT (table design)

Post by Antti »

Short jump cannot jump very far because the offset is signed (8-bit). Your startbs should be right after the BPB.
User avatar
BASICFreak
Member
Member
Posts: 284
Joined: Fri Jan 16, 2009 8:34 pm
Location: Louisiana, USA

Re: Confused on FAT (table design)

Post by BASICFreak »

Antti wrote:Short jump cannot jump very far because the offset is signed (8-bit). Your startbs should be right after the BPB.
By signed 8bit you mean 0xxxxxxx which means a short jump can only go 127 bytes instead of 255; correct?

and thanks for that quick reply.
BOS Source Thanks to GitHub
BOS Expanded Commentary
Both under active development!
Sortie wrote:
  • Don't play the role of an operating systems developer, be one.
  • Be truly afraid of undefined [behavior].
  • Your operating system should be itself, not fight what it is.
User avatar
bluemoon
Member
Member
Posts: 1761
Joined: Wed Dec 01, 2010 3:41 am
Location: Hong Kong

Re: Confused on FAT (table design)

Post by bluemoon »

My advice is to always read the manual if uncertain:
Instruction Manual Vol2 - JMP:
Short jump—A near jump where the jump range is limited to –128 to +127 from the current EIP value.
Note that EIP is advanced to the next instruction before performing the jmp, so a short jmp of 0 basically has no effect, and you could jmp to -128/+127 bytes calculated from the point after the jmp instruction.
User avatar
~
Member
Member
Posts: 1228
Joined: Tue Mar 06, 2007 11:17 am
Libera.chat IRC: ArcheFire

Re: Confused on FAT (table design)

Post by ~ »

bluemoon wrote:My advice is to always read the manual if uncertain:
Instruction Manual Vol2 - JMP:
Short jump—A near jump where the jump range is limited to –128 to +127 from the current EIP value.
Also read the Intel and AMD CPU manuals. I remember that by doing so, it can be seen that one of the manuals explains better some instructions than the other in a lot of cases.

Note that EIP is advanced to the next instruction before performing the jmp, so a short jmp of 0 basically has no effect, and you could jmp to -128/+127 bytes calculated from the point after the jmp instruction.


Then it looks like the jmp instruction bytes are processed (atomically).

First the main opcode is read (0xEB) and recognized as a short jump. Then IP/EIP/RIP is increased in 1.

Then it is recognized that one more byte has to be read. It is read and taken as offset. Then IP/EIP/RIP is increased in 1.

After this, what remains to do from the jmps is to add/substract the specified unsigned 8-bit offset to IP/EIP/RIP.

So if we used jmps -2 we would create an infinite loop; and if we used jmps 0, it would have been usually better to just execute a nop instead.

And if we used jmps -1 (or any other value that would cause to misalign the IP/EIP/RIP relative to the current code), we would end up turning the instructions into garbage because we would start arbitrarily in the middle of some instruction, not at its beginning.
________________________________________________
________________________________________________
________________________________________________
________________________________________________



This is the FAT12 boot code I use, which took me a lot to adapt from Bootf02 (Public Domain):

Note that the instructions at the start are more easily written manually since some assemblers accept jmp short and others accept jmps:

Code: Select all

_00h_jmp: db 0EBh                         ;jmps 003E
          db 03Ch                         ;2                        (2)
_02h_nop: nop                             ;1                        (3)

Code: Select all

%define resbytes 510-(unused-_00h_jmp)

ORG 7C00h


_00h_jmp: db 0EBh                         ;jmps 003E
          db 03Ch                         ;2                        (2)
_02h_nop: nop                             ;1                        (3)

_03h_OEMid              db    "OEMIdent"  ;8                        (11)
_0Bh_bytesPerSect       dw         0200h  ;2                        (13)
_0Dh_sectsPerClus       db          001h  ;1                        (14)
_0Eh_resrvedSects       dw         0001h  ;2                        (16)
_10h_numOfFATs          db          002h  ;1                        (17)
_11h_numRootDirEntries  dw         00E0h  ;2                        (19)
_13h_numSectors         dw         0B40h  ;2                        (21)
_15h_mediaType          db          0F0h  ;1                        (22)
_16h_numFATsectors      dw         0009h  ;2                        (24)
_18h_sectorsPerTrack    dw         0012h  ;2                        (26)
_1Ah_numHeads           dw         0002h  ;2                        (28)
_1Ch_numHiddenSects     dd     00000000h  ;4                        (32)
_20h_numSectorsHuge     dd     00000000h  ;4                        (36)
_24h_driveNumber        db           00h  ;1                        (37)
_25h_reserved           db           00h  ;1                        (38)
_26h_signature          db           29h  ;1                        (39)
_27h_volumeID           db        "????"  ;4                        (43)
_28h_volumeLabel        db "VolumeLabel"  ;11                       (54)
_36h_FSType             db    "FAT12   "  ;8                        (62)





;This is exactly where we jump to:
;;

;INIT: 448 free bytes:
;INIT: 448 free bytes:
;INIT: 448 free bytes:
;   pusha

;    mov al,18   ;640x480x16 mode
;    mov ah,0   ;service
;     int 10h

;   popa

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

   ;Force floppy A:
  ;;
    xor dx,dx


  start:  cli                             ;{0}
          lgdt    [cs:GDT]              ;Load GDT. This is how we would
                                          ;exactly access the GDT in
                                          ;real mode
            mov     ecx, CR0                ;Switch to protected mode
            inc     cx            ;set PE bit
            mov     CR0, ecx          ;{5} here we activate protected mode
 ;END:  enable protected mode (time 1 of 2) to load GDT
 ;END:  enable protected mode (time 1 of 2) to load GDT
 ;END:  enable protected mode (time 1 of 2) to load GDT








;;INIT: enable A20
;;INIT: enable A20
;;INIT: enable A20
  ;registers modified in this INIT--END portion:
   ;AX (EAX)
     ;registers with values to reuse in the next INIT--END portion:
      ;AH (cleared to 0)





  .5:     in      al, 0x64              ;Enable A20 {4A}. Port 0x64 is the
                                        ;KBC port at the motherboard.

          test    al, 2     ;See if bit 2 at this port is 1, which means
                            ;that he KBC is not ready.

          jnz     .5    ;Repeat until but 2 of port 0x64 is 0, which means
                        ;that the KBC is ready for commands.

        mov     al, 0xD1    ;This command is to write the status byte.
                            ;This is the so-called *WRITE OUTPUT PORT*.
          out     0x64, al    ;Here we send it and it gets executed.

.6:     in      al, 0x64    ;Read the byte at port 0x64.
        and     ax, byte 2   ;See if this bit is 0.
                             ;NOTE: this will leave AL to 0 at once, which
                             ;      will be used in the next
                             ;      INIT--END block.
          jnz     .6           ;Repeat until the KBC is ready
                               ;(bit 2 to 0)


        mov     al, 0xDF    ;Set the configuration bits to send.

            out     0x60, al   ;Send this parameter to the data port
                               ;of the KBC. At this point is where the
                               ;A20 line is enabled.
;;END:  enable A20
;;END:  enable A20
;;END:  enable A20














 ;;INIT: configuration of memory and register parameters
 ;;INIT: configuration of memory and register parameters
 ;;INIT: configuration of memory and register parameters
  ;registers that are modified in this INIT--END portion:
   ;AX (EAX) 0
   ;DS 0
   ;ES 0x800
   ;SS 0
   ;SP 0x800

     ;registers with values to reuse in the next INIT--END portion:
      ;apparently ALL of the previous ones

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

        mov     al, SELDat32            ;Selector for 4Gb data seg. What we do here
                                        ;is to take the address of the second selector
                                        ;of the GDT.
                                        ;We are using the 8-bit register AL to hold the
                                        ;16-bit data selector number because AH is
                                        ;already set to 0, and with this we save 1 byte
                                        ;or so of boot space.


        mov     ds, ax                  ;{2} Extend limit for ds. Typically
                                        ;would get the value 0010h. (16)
        mov     es, ax                  ;Extend limit for es. ES would also
                                        ;be set to 16.

        dec     cx                      ;Switch back to real mode. From the start, ECX
                                        ;contained the value of CR0 with PE
                                        ;bit set. Here we disable the PE bit again,
                                        ;and we put it into CR0 in the next
                                        ;instruction.
	mov	CR0, ecx		;{5}
        sti     ;v2012-05-31


  ;Here we are in Real Mode:
  ;Here we are in Real Mode:
  ;Here we are in Real Mode:
        mov     [_00h_jmp], dl         ;Save drive number we came from. Since
                                       ;we won't use again the first byte of code from
                                       ;the boot, the byte of *jmp 03Eh* instruction,
                                       ;we will use that byte as the variable space for
                                       ;the disk number. We must recognize that this is
                                       ;pretty clever.

        mov     sp, 0x800              ;{1B}. Configure the end of stack at 0x800

        xor     eax, eax                ;Segment. 32 bits set to 0
        mov     ds, ax                  ;DS (Data Segment) set to 0
        mov     ss, ax                  ;SS (Stack Segment) set to 0
        mov     es, sp                  ;Read directory at 800:0 {1C}. ES
                                        ;(Extra Segment) 0x800. Apparently we use
                                        ;ES:DS or ES:SS to access the disk.
                                        ;By now, the conflict that seems to be here
                                        ;with the sack doesn't matter much, since we
                                        ;won't save (much) data nor make calls to
                                        ;routines.
 ;;END:  configuration of memory and register parameters
 ;;END:  configuration of memory and register parameters
 ;;END:  configuration of memory and register parameters











 ;;INIT: Configure disk information
 ;;INIT: Configure disk information
 ;;INIT: Configure disk information
  ;>   eax = 00000000

  ;Here we are still in Real Mode since the previous INIT--END:
  ;Here we are still in Real Mode since the previous INIT--END:
  ;Here we are still in Real Mode since the previous INIT--END:
        mov     al, [_10h_numOfFATs]      ;Number of FATs
        mul     byte [_16h_numFATsectors] ;Times size of FAT |(in sectors?)
        add     ax, [_0Eh_resrvedSects]   ;Plus Sectors before first FAT
                 ;(_10h_numOfFATs*_16h_numFATsectors)+_0Eh_resrvedSects
					;eax = LBN of Root directory

        movzx   edi,word [_11h_numRootDirEntries] ;Root directory entries
	push	di			; used again later
	dec	di			;Convert to number of sectors
                                          ;Then, this means that
                                          ;_11h_numRootDirEntries-1 is equals to
                                          ;the number of sectors. But exactly why?
                                          ;Maybe every sector represents an entry.

        shr     di, 4               ;16 directory entries per sector
	inc	di

        call    read_sectors    ;Call to ahead address
 ;;END:  Configure disk information
 ;;END:  Configure disk information
 ;;END:  Configure disk information












 ;;INIT: Search file name in the root directory
 ;;INIT: Search file name in the root directory
 ;;INIT: Search file name in the root directory
  ;>  eax  = LBN of root directory
  ;>  edi  = length of root directory in sectors
  ;>  [sp] = length of root directory in entries
  ;>  esi  = 00000000

  ;Here we are still in Real Mode since the past 2 INIT--END blocks:
  ;Here we are still in Real Mode since the past 2 INIT--END blocks:
  ;Here we are still in Real Mode since the past 2 INIT--END blocks:
	lea	ebp, [eax+edi]		;ebp = LBN of cluster 2

        pop     bx                      ;Root directory entries. Recover the value
                                        ;of DI stored in BX
        xor     di, di               ;Point at directory {1C}
  .20:  mov     si, kernelFile       ;Name of file we want. We take the 16-bit
                                     ;address of the string.
	xor	ecx, ecx
        mov     cl, 11       ;Number of bytes to read (length of the string
                             ;"KERNEL  BIN")
        a32 rep cmpsb                   ;Found the file?. Here is where 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   ;According to the result of a bit in FLAGS, produced by
                      ;*dec bx*. Concretely the bit that indicates that the operation
                      ;has set the value of the operand down to 0.

	;Couldn't find file in directory
  boot_error:
  disk_error: 
	mov	ax, 0xE07		;{3}
        int     10h          ;Video service. Here we will "ring" the
                             ;bell.
        jmp short $     ;Since this in an error, we create a loop that stops
                        ;the operation of the machine.
 ;;END:  Search file name in the root directory
 ;;END:  Search file name in the root directory
 ;;END:  Search file name in the root directory









 ;;INIT: Read the file according to what the previous INIT--END found
 ;;INIT: Read the file according to what the previous INIT--END found
 ;;INIT: Read the file according to 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, [_16h_numFATsectors] ;Size of FAT (in sectors)
          mov     ax, [_0Eh_resrvedSects]  ;LBN of FAT
            call    read_sectors    ;Call to ahead address

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


















 ;;INIT: Final processes, configuration of paging and pass control to the kernel
 ;;INIT: Final processes, configuration of paging and pass control to the kernel
 ;;INIT: Final processes, configuration of paging and pass control to the kernel
  .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, [_0Dh_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



 ;;;INIT: paging
 ;;;INIT: paging
 ;;;INIT: paging
  ;>     eax = 0
  ;>     edx = 0000????
  ;>      bx = 0FF?

  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, 00000111b ;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
	or	eax, 0x00000001    ;v2012-05-31
        cli     ;v2012-05-31
	mov	CR0, eax
        mov     cl, SELDat32            ;Setup ds and es
	push	cx			;{5}
	pop	ds
	mov	es, cx
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;        jmp dword SELCod32:0xFF800000   ;Go
     a32   jmp dword SELCod32:0x100000   ;Go
 ;;;END:  paging
 ;;;END:  paging
 ;;;END:  paging


 ;;END:  Final processes, configuration of paging and pass control to the kernel
 ;;END:  Final processes, configuration of paging and pass control to the kernel
 ;;END:  Final processes, configuration of paging and pass control to the kernel






















 ;;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 [_18h_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, [_1Ah_numHeads]
          div     ebx             ;EAX=cylinder ;EDX=head

          mov     dh, dl          ;Head
          mov     dl, [_00h_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:
   _SELNull equ 0   ;WARNING: This selector, besides being the pointer to the GDT
        GDT_size:   ;         is the null selector.
        dw GDTsize
        GDT_actualptr:
        dd GDT
       dw 0x0000

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

   _SELDat32 equ 16  ;this is the "plain data selector"
     dw 0FFFFh       ; bits 0-15 length
     dw 00000h       ; bits 0-15 base address
     db 0            ; bits 16-23 base address
     db 10010010b    ; bits P,DPL,DT and type
     db 11001111b    ; bits G,D and bits 16-19 length
     db 0            ; bits 24-31 base address
   GDT_end:

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

  unused: times resbytes db 0x55

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


_1F_55AA_signature      dw 0xAA55         ;2                        (512)



SELNull  equ 0
SELCod32 equ 8
SELDat32 equ 16
Post Reply