LogicalDiskAbsoluteAccessEx | DISKVIEW | FRAGVIEW | DEFRAG

DOS specific questions.
Post Reply
DOS386
Posts: 798
Joined: Jul 02, 2005 20:55

LogicalDiskAbsoluteAccessEx | DISKVIEW | FRAGVIEW | DEFRAG

Post by DOS386 »

Code: Select all

'' --------------------------------------------------------------------

'' ### DISK VIEWER (R) ###
'' (CL) 2008 by DOS386 | Public Domain | ABUSE at your own risk !!!
'' DOS only !!! | Requires a recent DOS kernel (FreeDOS, EDR-DOS)

'' --------------------------------------------------------------------

#include "dos/go32.bi" '' DPMI stuff declarations

type UINT32  as UINTEGER
type UINT8   as UBYTE
type PUINT8P as UBYTE PTR

declare sub SECTEX (BYVAL AS UINT32, BYVAL AS UINT32)

DIM SHARED AS UINT32  DDS , LTB , STB
DIM SHARED AS PUINT8P MYBUF
DIM SHARED AS UINT32  VGN32MYBUF, VGN32MYPOS, VGN32SEC
DIM SHARED AS STRING  VGSLINE1, VGSLINE2
DIM SHARED AS UINT8   AA

'' --------------------------------------------------------------------

'' Init GO32
DDS = _go32_info_block.selector_for_linear_memory
LTB = _go32_info_block.linear_address_of_transfer_buffer

MYBUF=ALLOCATE(512)
VGN32MYBUF=CAST(UINT32,MYBUF)
? HEX$(VGN32MYBUF) : ?
VGN32SEC=0

DO
  ? "Sector: " + STR$(VGN32SEC) + " | [SPACE] -> next | [P] -> previous | [ESC] -> ???" : ?
  SECTEX (VGN32SEC,VGN32MYBUF)
  VGN32MYPOS=0
  DO
    IF ((VGN32MYPOS AND 15)=0) THEN 
      VGSLINE1=HEX$(VGN32MYPOS)+" : " : VGSLINE2=" "
      IF LEN(VGSLINE1)=4 THEN VGSLINE1="00" + VGSLINE1
      IF LEN(VGSLINE1)=5 THEN VGSLINE1="0"  + VGSLINE1
    ENDIF
    AA=PEEK(VGN32MYBUF+VGN32MYPOS)
    VGN32MYPOS=VGN32MYPOS+1
    IF (AA<16) THEN 
      VGSLINE1=VGSLINE1 + "0" 
    ENDIF
    VGSLINE1=VGSLINE1 + HEX$(AA) + " " 
    IF ((AA<32) OR (AA>126)) THEN AA=46 
    VGSLINE2=VGSLINE2+CHR$(AA)
    IF ((VGN32MYPOS AND 15)=0) THEN ? VGSLINE1+VGSLINE2
    IF (VGN32MYPOS=512) THEN EXIT DO
  LOOP
  ?
  DO
    AA=ASC(INKEY$)
    IF (AA=112) THEN AA=80 '' UCASE$("P")
    IF ((AA=27) OR (AA=32) OR (AA=80)) THEN EXIT DO
  LOOP
  IF (AA=27) THEN EXIT DO
  IF (AA=32) THEN VGN32SEC=VGN32SEC+1
  IF ((AA=80) AND (VGN32SEC<>0)) THEN VGN32SEC=VGN32SEC-1
LOOP
 
END

'' --------------------------------------------------------------------

SUB SECTEX (BYVAL VLN32SEC AS UINT32, BYVAL VLN32ADDR AS UINT32)

'' Logical disk "absolute" sector read - INT $21/$7305
''
'' IN:  ???
'' OUT: ???
''
'' Memory: 0:   $32 bytes INT $31 | $32: $0E bytes wasted 
''         $40: 6 bytes "packet"  | $46: $0A bytes wasted
''         $50: 1.5 KiB stack     | $650: buffer
''
'' Uses globals: LTB (linear addr of buffer) and DDS (ZERO-based selector)

  ASM

      mov  edi,[LTB]   '' For clear (2 KiB) and INT (based on ES, size=$32)
      mov  eax,[DDS]
      push eax
      pop  es          '' !!! Trashing ES
      cld

      xor  eax,eax     '' For DPMI simulant INT $31 and clearing
      xor  ecx,ecx     '' & 
      mov  ch,2        '' & MOVNTQ ECX,512
      push edi
      rep  stosd       '' [ES:EDI] ZERO'izing 2 KiB | side effect: ECX==0
      pop  edi

      mov  ah,3        '' @ For DPMI simulant INT $31 / $0300 see far below
      mov  bl,0x21     '' @ BL=$21 | Don't touch AX and BX below
      mov  bh,0        '' @ BH=0 (crap flags)

      dec  ecx 
      mov  [es:edi+0x18],ecx '' CX / ECX = $FFFF
      inc  ecx               '' !!! see below
      mov  cx,0x7305         '' % "absolute" thing
      mov  [es:edi+0x1C],cx  '' % AX
      mov  ecx,edi           '' @ Linear
      shr  ecx,4             '' @ To segment | high 16 bits==0
      add  ecx,4             '' @ Skip $32 -> $40 bytes | high 16 bits ==0
      mov  [es:edi+0x24],cx  '' @ Segment address of "packet" (OFF***=0)  
      inc  ecx               '' @ Now + $50
      mov  [es:edi+0x30],cx  '' @ SS
      add  ecx,0x60          '' @ Now + $0650 | Buffer starts $610 bytes after 
      mov  [es:edi+0x48],cx  '' @ Buffer segment address in "packet" (OFF***=0)
      mov  dh,6              '' & 1.5 KiB stack
      mov  [es:edi+0x2F],dh  '' & SP high byte
      mov  dl,3              '' Drive "C:"
      mov  [es:edi+0x14],dl  '' DL
      mov  edx,[VLN32SEC]
      mov  [es:edi+0x40],edx '' Sector number
      mov  dl,1
      mov  [es:edi+0x44],dl  '' Amount of sectors
     
      pushf
      pop  edx
      mov  [es:edi+0x20],dl  '' FLAGS 16-bit only, we poke only 8-bit

      xor  ecx,ecx           '' MOVNTQ ECX,0
      int  0x31              '' AX==$0300 | BX==$21 see far above

      mov  edi,[LTB]         '' Again ??? Required ???
      mov  eax,[DDS]
      push eax
      pop  es                '' !!! Trashing ES
      cld

      mov  bl,[es:edi+0x20]  '' FLAGS
      shr  bl,1              '' Now we have it in flag (C)
      jnc  xx1               '' OK
      ud2

xx1:  mov  esi,[VLN32ADDR] '' & Our destination, but for now in ESI !!!
      xchg esi,edi         '' & Fix ^^^ it 
      add  esi,0x0650      '' & Skip DPMI simulant structure + more garbage
      push ds              '' @ non-ZERO
      push es              '' @ ZERO | SWAP DS,ES | No "XCHG DS,ES" :-(
      pop  ds              '' @ ZERO
      pop  es              '' @ non-ZERO
      xor  ecx,ecx         '' & MOVNTQ ECX, $80
      mov  cl,0x80         '' & -> $0200 bytes
      rep  movsd           '' [ES:EDI]<-[DS:ESI] | ESI and EDI trashed
      push es              '' @
      pop  ds              '' @ Crucial !!!

  END ASM

END SUB

'' --------------------------------------------------------------------

'' INT $21 / $7305
'' FreeDOS, EDR-DOS (Windaube95) - FAT32 - EXTENDED ABSOLUTE DISK READ/WRITE
'' AX = $7305
'' CX = $FFFF
'' DL = drive number (1=A:, etc.)
'' SI = read/write mode flags (see #01791)
'' Bitfields for Extended Absolute Disk Read/Write mode flags:
'' Bit(s)   Description (Table 01791)
''  0       direction (0=read, 1=write)
''  12-1    reserved (0)
''  14-13   write type (should be 00 on reads)
''          00      unknown data
''          01      FAT data
''          10      directory data
''          11      file data
''  15      reserved (0)
'' Format of disk read packet:
'' DS:BX -> disk I/O packet (see #02548 at INT 25)
'' Offset Size Description (Table 02548)
'' 0 DWORD  sector number
'' 4 WORD   number of sectors to read 
'' 6 DWORD  transfer address OFF:SEG ???
'' Return: CF clear if successful
''         CF set on error
''         AX = error code
'' Note: one can not specify the default drive (DL=0) for this function.

'' --------------------------------------------------------------------

'' INT $31 / $0300
'' $00  DWORD   EDI
'' $04  DWORD   ESI
'' $08  DWORD   EBP
'' $0C  DWORD   reserved (0)
'' $10  DWORD   EBX
'' $14  DWORD   EDX
'' $18  DWORD   ECX
'' $1C  DWORD   EAX
'' $20  WORD    flags
'' $22  WORD    ES
'' $24  WORD    DS
'' $26  WORD    FS
'' $28  WORD    GS
'' $2A  WORD    IP
'' $2C  WORD    CS
'' $2E  WORD    SP
'' $30  WORD    SS
'' $32  END :-)

'' --------------------------------------------------------------------
Probably won't work with obsolete kernels (MS-DOG, closed/open DR-DOS), even less in NTV-DM (ways too ultraparanoid to allow "evil old 16-bit MS-DOS applications" to even read from your HD :-D ).

FYI: It's a NEW 32-bit DOS example / "application"

Lacks:
- no write
- only 1 sector per call
- no disk size overflow check (at least sector 0 underflow is checked)
- lousy error handling

Should work with any intact DPMI host or extender (D3X, WDOSX, HDPMI32, CWSDPMI (?) ).

So if someone wants to code a disk editor (no big need, we have WDe disk editor by Ben Cadieux and HDEDIT by Japheth ), or a Defrag (big need, FreeDOS DEFRAG still doesn't really work), this is the starting point ;-)

EDIT : enhanced thread subject
Last edited by DOS386 on Jul 21, 2008 3:49, edited 1 time in total.
DOS386
Posts: 798
Joined: Jul 02, 2005 20:55

Post by DOS386 »

Code: Select all

'' --------------------------------------------------------------------

'' ### FRAGMENT VIEWER (R) ###
'' (CL) 2008 by DOS386 | Public Domain | ABUSE at your own risk !!!
'' DOS only !!! | Requires a recent DOS kernel (FreeDOS, EDR-DOS)

'' --------------------------------------------------------------------

#include "dos/go32.bi" '' DPMI stuff declarations

type UINT32  as UINTEGER
type UINT16  as USHORT
type UINT8   as UBYTE
type PUINT8P as UBYTE PTR

declare sub DUMP

declare sub SECTEX (BYVAL AS UINT32, BYVAL AS UINT32)

DIM SHARED AS PUINT8P MYBUF, FATBUF
DIM SHARED AS UINT32  VGN32MYBUF, VGN32FATBUF

DIM SHARED AS UINT32  DDS , LTB 

DIM SHARED AS UINT8   AA, BB, CC
DIM SHARED AS UINT16  KKK, LLL
DIM SHARED AS UINT32  QQQQ, RRRR, SSSS

DIM SHARED AS UINT8   VGN32SPC '' Sectors per cluster
DIM SHARED AS UINT32  VGN32FATSIZE, VGN32FATBYTES, VGN32ROOTSTART
DIM SHARED AS UINT32  VGN32CLUST '' Sector where "cluster 0" begins
DIM SHARED AS UINT32  VGN32RESERVED '' Reversed sextors (incl. boot)
DIM SHARED AS UINT32  VGN32MYPOS
DIM SHARED AS UINT32  VGN32FILE
DIM SHARED AS UINT32  VGN32FRAGS

DIM SHARED AS STRING  VGSLINE1, VGSLINE2, VGSFILE

'' --------------------------------------------------------------------

VGSFILE="LEAKEDXPPAQ" '' 11 chars

'' Init GO32
DDS = _go32_info_block.selector_for_linear_memory
LTB = _go32_info_block.linear_address_of_transfer_buffer

? : ? "FRAGMENT VIEWER (R)" : ?
MYBUF=ALLOCATE(512)
VGN32MYBUF=CAST(UINT32,MYBUF)
IF (VGN32MYBUF=0) THEN ASM UD2

? "Reading B.S. :-D ... ";
SECTEX (0,VGN32MYBUF)
? "Done !" : ?

KKK=PEEK(UINT16,VGN32MYBUF+11)
? "Bytes per sector:    " ; KKK
AA=PEEK(VGN32MYBUF+13)
? "Sectors per cluster: " ; AA
VGN32SPC=CAST(UINT32,AA)
? "* Cluster size :     " ;
IF (AA=1) THEN
  ? "512 Bytes"
ELSE
  ? (AA SHR 1) ; " KiB"
ENDIF
KKK=PEEK(UINT16,VGN32MYBUF+14)
? "Reserved sectors:    " ; KKK
VGN32RESERVED=CAST(UINT32,KKK)
AA=PEEK(VGN32MYBUF+16)
? "Number of FAT's:     " ; AA
KKK=PEEK(UINT16,VGN32MYBUF+19)
? "Total sectors FAT12/FAT16: " ; KKK
QQQQ=PEEK(UINT32,VGN32MYBUF+32)
? "Total sectors FAT16/FAT32: " ; QQQQ
VGN32FATSIZE=PEEK(UINT32,VGN32MYBUF+36)
? "FAT size in sectors FAT32: " ; VGN32FATSIZE
VGN32FATBYTES=VGN32FATSIZE SHL 9
? "* FAT size in bytes FAT32: " ; VGN32FATBYTES
VGN32ROOTSTART=PEEK(UINT32,VGN32MYBUF+44)
? "Root start cluster FAT32:  " ; VGN32ROOTSTART
VGN32CLUST=VGN32RESERVED+(VGN32FATSIZE SHL 1)-(VGN32SPC SHL 1)
? "* Start sector of ""cluster 0"" FAT32: " ; VGN32CLUST
? : SLEEP

FATBUF=ALLOCATE(VGN32FATBYTES)
VGN32FATBUF=CAST(UINT32,FATBUF)
IF (VGN32FATBUF=0) THEN ASM UD2

? "Reading F.A.T. :-D "
QQQQ=0
DO
  IF (QQQQ=VGN32FATSIZE) THEN EXIT DO
  SECTEX (VGN32RESERVED+QQQQ,VGN32MYBUF)
  ASM
    mov  esi, [VGN32MYBUF]
    mov  edi, [VGN32FATBUF]
    mov  eax, [QQQQ]
    shl  eax, 9
    add  edi, eax
    xor  ecx, ecx
    mov  cl, 0x80  '' MOVNTQ ECX, $80 -> 512 bytes
    rep  movsd    
  END ASM
  IF QQQQ<256 THEN
    ? ".";
  ELSE
    IF ((QQQQ AND 255)=0) THEN ? "*";
  ENDIF
  QQQQ=QQQQ+1
LOOP
? " Done !" : ? : SLEEP

? "Reading main directory :-D " : ?
VGN32FILE=0 : QQQQ=VGN32ROOTSTART '' QQQQ walks cluster chain
DO
  RRRR=0 '' Counts sextors in cluster  
  ? "Cluster: $"; HEX$(QQQQ)
  DO
    IF (RRRR=VGN32SPC) THEN EXIT DO
    SECTEX (VGN32CLUST+(QQQQ*VGN32SPC)+RRRR,VGN32MYBUF)
    RRRR=RRRR+1
    DUMP : ? : SLEEP
    VGN32MYPOS=0
    DO
      IF ((VGN32MYPOS AND 15)=0) THEN VGSLINE1="" 
      AA=PEEK(VGN32MYBUF+VGN32MYPOS)
      VGSLINE1=VGSLINE1+CHR$(AA)
      IF VGSLINE1=VGSFILE THEN
        ? "L&G, we got him !!! "; '' Now pos 10=$0A | 20=$14 HI | 26=$1A LO
        KKK=PEEK(UINT16,VGN32MYBUF+VGN32MYPOS+10)        
        LLL=PEEK(UINT16,VGN32MYBUF+VGN32MYPOS+16)          
        VGN32FILE=(KKK SHL 16) + LLL
        ? "Cluster: $" ; HEX$(VGN32FILE)
        ? : SLEEP
      ENDIF
      VGN32MYPOS=VGN32MYPOS+1
      IF (VGN32MYPOS=512) THEN EXIT DO
    LOOP
  LOOP
  QQQQ=PEEK(UINT32,VGN32FATBUF+(QQQQ SHL 2))
  ? "Next FAT entry: $" + HEX$(QQQQ)
  IF (QQQQ OR &HF0000000)=&HFFFFFFFF THEN EXIT DO
LOOP
? "Done !" : ? : SLEEP

IF (VGN32FILE=0) THEN ASM UD2

? "Inspecting file fragmentation :-D " : ?
QQQQ=VGN32FILE : VGN32FRAGS=1 : AA=200 : CC=0
VGN32MYPOS=0 '' Here MYPOS counts clusters
DO
  RRRR=PEEK(UINT32,VGN32FATBUF+(QQQQ SHL 2)) '' QQQQ this | RRRR next
  BB=0  
  IF (RRRR OR &HF0000000)=&HFFFFFFFF THEN BB=1
  SSSS=(VGN32MYPOS*VGN32SPC) SHL 9 '' Byte position
  IF (RRRR<>(QQQQ+1)) THEN AA=200 '' Frag or EOF
  IF (AA>190) THEN
    IF (CC=1) THEN ?
    ? "Cluster pos: $"+HEX$(VGN32MYPOS)+" this cluster: $"+HEX$(QQQQ);
    ? " next FAT entry: "+HEX$(RRRR)
    ? "Byte position: "+STR$(SSSS)+" = $"+HEX$(SSSS)+" = "+STR$(SSSS SHR 20);
    ? " MiB | frags so far: "+HEX$(VGN32FRAGS)
    CC=0 : AA=AA-1: SLEEP 100
  ELSE
    IF (AA<>0) THEN
      CC=1 : AA=AA-1: ? ".";
      IF (AA=0) THEN ? "?";
    ENDIF
  ENDIF
  IF ((RRRR<>(QQQQ+1)) AND (BB=0)) THEN
    VGN32FRAGS=VGN32FRAGS+1
    ? "!!! New fragment will follow!!!" 
    SLEEP 500
  ENDIF
  IF (BB=1) THEN EXIT DO
  VGN32MYPOS=VGN32MYPOS+1
  QQQQ=RRRR 
LOOP
? "EOF -> Done !" : ?

DO
  VGSLINE1=INKEY$
  IF VGSLINE1="" THEN EXIT DO
LOOP

END

'' --------------------------------------------------------------------

SUB DUMP

  VGN32MYPOS=0
  DO
    IF ((VGN32MYPOS AND 15)=0) THEN 
      VGSLINE1=HEX$(VGN32MYPOS)+" : " : VGSLINE2=" "
      IF LEN(VGSLINE1)=4 THEN VGSLINE1="00" + VGSLINE1
      IF LEN(VGSLINE1)=5 THEN VGSLINE1="0"  + VGSLINE1
    ENDIF
    AA=PEEK(VGN32MYBUF+VGN32MYPOS)
    VGN32MYPOS=VGN32MYPOS+1
    IF (AA<16) THEN 
      VGSLINE1=VGSLINE1 + "0" 
    ENDIF
    VGSLINE1=VGSLINE1 + HEX$(AA) + " " 
    IF ((AA<32) OR (AA>126)) THEN AA=46 
    VGSLINE2=VGSLINE2+CHR$(AA)
    IF ((VGN32MYPOS AND 15)=0) THEN ? VGSLINE1+VGSLINE2
    IF (VGN32MYPOS=512) THEN EXIT DO
  LOOP

END SUB

'' --------------------------------------------------------------------

SUB SECTEX (BYVAL VLN32SEC AS UINT32, BYVAL VLN32ADDR AS UINT32)

'' Logical disk "absolute" sector read - INT $21/$7305
''
'' IN:  ???
'' OUT: ???
''
'' Memory: 0:   $32 bytes INT $31 | $32: $0E bytes wasted 
''         $40: 6 bytes "packet"  | $46: $0A bytes wasted
''         $50: 1.5 KiB stack     | $650: buffer
''
'' Uses globals: LTB (linear addr of buffer) and DDS (ZERO-based selector)

  ASM

      mov  edi,[LTB]   '' For clear (2 KiB) and INT (based on ES, size=$32)
      mov  eax,[DDS]
      push eax
      pop  es          '' !!! Trashing ES
      cld

      xor  eax,eax     '' For DPMI simulant INT $31 and clearing
      xor  ecx,ecx     '' & 
      mov  ch,2        '' & MOVNTQ ECX,512
      push edi
      rep  stosd       '' [ES:EDI] ZERO'izing 2 KiB | side effect: ECX==0
      pop  edi

      mov  ah,3        '' @ For DPMI simulant INT $31 / $0300 see far below
      mov  bl,0x21     '' @ BL=$21 | Don't touch AX and BX below
      mov  bh,0        '' @ BH=0 (crap flags)

      dec  ecx 
      mov  [es:edi+0x18],ecx '' CX / ECX = $FFFF
      inc  ecx               '' !!! see below
      mov  cx,0x7305         '' % "absolute" thing
      mov  [es:edi+0x1C],cx  '' % AX
      mov  ecx,edi           '' @ Linear
      shr  ecx,4             '' @ To segment | high 16 bits==0
      add  ecx,4             '' @ Skip $32 -> $40 bytes | high 16 bits ==0
      mov  [es:edi+0x24],cx  '' @ Segment address of "packet" (OFF***=0)  
      inc  ecx               '' @ Now + $50
      mov  [es:edi+0x30],cx  '' @ SS
      add  ecx,0x60          '' @ Now + $0650 | Buffer starts $610 bytes after 
      mov  [es:edi+0x48],cx  '' @ Buffer segment address in "packet" (OFF***=0)
      mov  dh,6              '' & 1.5 KiB stack
      mov  [es:edi+0x2F],dh  '' & SP high byte
      mov  dl,3              '' Drive "C:"
      mov  [es:edi+0x14],dl  '' DL
      mov  edx,[VLN32SEC]
      mov  [es:edi+0x40],edx '' Sector number
      mov  dl,1
      mov  [es:edi+0x44],dl  '' Amount of sectors
     
      pushf
      pop  edx
      mov  [es:edi+0x20],dl  '' FLAGS 16-bit only, we poke only 8-bit

      xor  ecx,ecx           '' MOVNTQ ECX,0
      int  0x31              '' AX==$0300 | BX==$21 see far above

      mov  edi,[LTB]         '' Again ??? Required ???
      mov  eax,[DDS]
      push eax
      pop  es                '' !!! Trashing ES
      cld

      mov  bl,[es:edi+0x20]  '' FLAGS
      shr  bl,1              '' Now we have it in flag (C)
      jnc  xx1               '' OK
      ud2

xx1:  mov  esi,[VLN32ADDR] '' & Our destination, but for now in ESI !!!
      xchg esi,edi         '' & Fix ^^^ it 
      add  esi,0x0650      '' & Skip DPMI simulant structure + more garbage
      push ds              '' @ non-ZERO
      push es              '' @ ZERO | SWAP DS,ES | No "XCHG DS,ES" :-(
      pop  ds              '' @ ZERO
      pop  es              '' @ non-ZERO
      xor  ecx,ecx         '' & MOVNTQ ECX, $80
      mov  cl,0x80         '' & -> $0200 bytes
      rep  movsd           '' [ES:EDI]<-[DS:ESI] | ESI and EDI trashed
      push es              '' @
      pop  ds              '' @ Crucial !!!

  END ASM

END SUB

'' --------------------------------------------------------------------

'' INT $21 / $7305
'' FreeDOS, EDR-DOS (Windaube95) - FAT32 - EXTENDED ABSOLUTE DISK READ/WRITE
'' AX = $7305
'' CX = $FFFF
'' DL = drive number (1=A:, etc.)
'' SI = read/write mode flags (see #01791)
'' Bitfields for Extended Absolute Disk Read/Write mode flags:
'' Bit(s)   Description (Table 01791)
''  0       direction (0=read, 1=write)
''  12-1    reserved (0)
''  14-13   write type (should be 00 on reads)
''          00      unknown data
''          01      FAT data
''          10      directory data
''          11      file data
''  15      reserved (0)
'' Format of disk read packet:
'' DS:BX -> disk I/O packet (see #02548 at INT 25)
'' Offset Size Description (Table 02548)
'' 0 DWORD  sector number
'' 4 WORD   number of sectors to read 
'' 6 DWORD  transfer address OFF:SEG ???
'' Return: CF clear if successful
''         CF set on error
''         AX = error code
'' Note: one can not specify the default drive (DL=0) for this function.

'' --------------------------------------------------------------------

'' INT $31 / $0300
'' $00  DWORD   EDI
'' $04  DWORD   ESI
'' $08  DWORD   EBP
'' $0C  DWORD   reserved (0)
'' $10  DWORD   EBX
'' $14  DWORD   EDX
'' $18  DWORD   ECX
'' $1C  DWORD   EAX
'' $20  WORD    flags
'' $22  WORD    ES
'' $24  WORD    DS
'' $26  WORD    FS
'' $28  WORD    GS
'' $2A  WORD    IP
'' $2C  WORD    CS
'' $2E  WORD    SP
'' $30  WORD    SS
'' $32  END :-)

'' --------------------------------------------------------------------

'' 00 : 03 "jmp"
'' 03 : 08 "oem"
'' UINT16  bytes_per_sector           /* $0B  11 */ "BPB" begins here
'' UINT8   sectors_per_cluster        /* $0D  13 */
'' UINT16  reserved_sectors           /* $0E  14 */
'' UINT8   number_of_fats             /* $10  16 */
'' UINT16  root_directory_entries     /* $11  17 */
'' UINT16  total_sectors              /* $13  19 */
'' UINT8   media_descriptor           /* $15  21 */
'' UINT16  sectors_per_fat            /* $16  22 */
'' UINT16  sectors_per_cylinder       /* $18  24 */
'' UINT16  number_of_heads            /* $1A  26 */
'' UINT32  hidden_sectors             /* $1C  28 */
'' UINT32  large_sector_count         /* $20  32 */
'' UINT32  fat_size_in_sectors        /* $24  36 */ "FAT32-BPB" beginds here
'' UINT16  ext_flags              (0) /* $28  40 */
'' UINT16  file_system_version    (0) /* $2A  42 */
'' UINT32  root_dir_start_cluster (2) /* $2C  44 */
'' UINT16  info_sector_number         /* $30  48 */
'' UINT16  backup_boot_sector         /* $32  50 */
'' UINT8   reserved_1[12]             /* $34  52 */
'' UINT8   drive_number      
'' UINT8   reserved          
'' UINT8   signature_byte    
'' UINT8   serial_number[4]  
'' UINT8   volume_label[11]  
'' UINT8   file_system_type[8]

'' --------------------------------------------------------------------
A step further: inspects fragmentation of a file :-)

Lacks:
- Drive C hardcoded
- Main directory only
- FAT32 only
- No error checking
Post Reply