Changeset 150 in xtideuniversalbios for trunk/XTIDE_Universal_BIOS/Inc


Ignore:
Timestamp:
Apr 29, 2011, 7:04:13 PM (13 years ago)
Author:
aitotat
google:author:
aitotat
Message:

Changes to XTIDE Universal BIOS:

  • Redesigned Disk Parameter Tables.
  • Code generalizations for supporting non-IDE devices in the future.
Location:
trunk/XTIDE_Universal_BIOS/Inc
Files:
1 added
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/XTIDE_Universal_BIOS/Inc/CustomDPT.inc

    r99 r150  
    55%define CUSTOMDPT_INC
    66
     7; Base DPT for all device types
     8struc DPT   ; 8 bytes
     9    ; General Disk Parameter Table related
     10    .wFlags                     resb    2
     11    .bIdevarsOffset             resb    1   ; Offset to IDEVARS for this drive
    712
    8 ; Base Disk Parameter Table for all hard disk drives.
    9 ; DPT might have extensions for specific functions.
    10 struc DPT
    11     ; General Disk Parameter Table related
    12     .bSize      resb    1   ; Size of DPT (with extensions) in bytes
    13     .wDrvNumAndFlags:
    14     .bDrvNum    resb    1   ; Drive number
    15     .bFlags     resb    1   ; DPT and Drive related flags
    16     .bReset     resb    1   ; Drive reset status (for debugging)
    17     .bIdeOff    resb    1   ; Offset to IDEVARS for this drive
     13    ; L-CHS to P-CHS and L-CHS to LBA28 conversion related
     14    .bLchsHeads                 resb    1   ; Number of L-CHS Heads (1...255)
    1815
    19     ; Lookup values for L-CHS to P-CHS and L-CHS to LBA28 conversions
    20     .bShLtoP    resb    1   ; Bit shift count for L-CHS to P-CHS conversion
    21     .wLHeads    resb    2   ; Number of L-CHS Heads (1...256)
    22 
    23     ; IDE related
    24     .wPCyls     resb    2   ; Number of P-CHS (IDE) Cylinders (1...16383)
    25     .wHeadsAndSectors:
    26     .bPHeads    resb    1   ; Number of P-CHS (IDE) Heads (1...16)
    27     .bPSect     resb    1   ; Number of P-CHS (IDE) Sectors per Track (1...63)
    28     .bDrvSel    resb    1   ; Drive Selection byte for Device/Head Register
    29     .bDrvCtrl   resb    1   ; Drive Control byte for Device Control Register
    30 
    31     ; Related to Block Mode transfers.
    32     ; Block size is specified in sectors (1, 2, 4, 8, 16, 32, 64 or 128).
    33     .wSetAndMaxBlock:
    34     .bSetBlock  resb    1   ; Currect block size (at least 1)
    35     .bMaxBlock  resb    1   ; Maximum block size, 0 = block mode not supported
     16    ; IDE Drive related
     17    .wPchsCylinders             resb    2   ; Number of P-CHS (IDE) Cylinders (1...16383)
     18    .wPchsHeadsAndSectors:
     19    .bPchsHeads                 resb    1   ; Number of P-CHS (IDE) Heads (1...16)
     20    .bPchsSectors               resb    1   ; Number of P-CHS (IDE) Sectors per Track (1...63)
    3621endstruc
    3722
    38 ; Bit definitions for DPT.bFlags
    39 MASK_DPT_ADDR       EQU     110b    ; Bits 1..2, Addressing Mode
    40 FLG_DPT_EBIOS       EQU     (1<<0)  ; EBIOS functions supported for this drive
    41 FLG_DPT_FIRSTPART   EQU     (1<<3)  ; First BIOS Partition of the drive (drive reset allowed)
    42 FLG_DPT_PARTITION   EQU     (1<<4)  ; BIOS Partition
    43 FLG_DPT_USERCHS     EQU     (1<<5)  ; User has specified P-CHS parameters
     23; DPT for ATA devices
     24struc DPT_ATA   ; 8 + 2 bytes = 10 bytes
     25    .dpt                        resb    DPT_size
    4426
    45 ; Values for different addressing modes (MASK_DPT_ADDR for DPT.bFlags)
    46 ADDR_DPT_LCHS       EQU     0       ; L-CHS Addressing Mode (NORMAL in many other BIOSes)
    47 ADDR_DPT_PCHS       EQU     1       ; P-CHS Addressing Mode (LARGE in many other BIOSes)
    48 ADDR_DPT_LBA28      EQU     2       ; 28-bit LBA Addressing Mode
    49 ADDR_DPT_LBA48      EQU     3       ; 48-bit LBA Addressing Mode
     27    ; Block size is specified in sectors (1, 2, 4, 8, 16, 32 or 64).
     28    ; 128 is not allowed to prevent offset overflow during data transfer.
     29    .wSetAndMaxBlock:
     30    .bSetBlock                  resb    1   ; Current block size (at least 1)
     31    .bMaxBlock                  resb    1   ; Maximum block size, 0 = block mode not supported
     32endstruc
    5033
    51 ; Bit definitions for DPT.bReset (inverted)
    52 FLG_RESET_nDRDY         EQU     (1<<0)  ; Drive ready to accept commands
    53 FLG_RESET_nINITPRMS     EQU     (1<<1)  ; Initialize Device Parameters successfull
    54 FLG_RESET_nRECALIBRATE  EQU     (1<<2)  ; Recalibrate successfull
    55 FLG_RESET_nSETBLOCK     EQU     (1<<3)  ; Initialize Block Mode successfull
    56 MASK_RESET_ALL          EQU     (FLG_RESET_nDRDY | FLG_RESET_nINITPRMS | FLG_RESET_nRECALIBRATE | FLG_RESET_nSETBLOCK)
     34LARGEST_DPT_SIZE                EQU     DPT_ATA_size
    5735
    5836
    59 ; Extended DPT for XTIDE Universal BIOS partitioned drive.
    60 ; This struct cannot exist with EDPT (EBIOS support).
    61 struc PART_DPT
    62     .dpt        resb    DPT_size
    63     .dwStartLBA:
    64     .twStartLBA resb    6   ; Starting 28- or 48-bit LBA for BIOS partition
    65 endstruc
     37; Bit definitions for DPT.wFlags
     38MASK_DPT_CHS_SHIFT_COUNT        EQU (7<<0)  ; Bits 0...3, P-CHS to L-CHS bit shift count (0...4)
     39FLG_DPT_SLAVE                   EQU FLG_DRVNHEAD_DRV    ; (1<<4), Drive is slave drive
     40MASK_DPT_ADDRESSING_MODE        EQU (3<<5)  ; Bits 5..6, Addressing Mode (bit 6 == FLG_DRVNHEAD_LBA)
     41FLG_DPT_ENABLE_IRQ              EQU (1<<7)
     42FLG_DPT_REVERSED_A0_AND_A3      EQU (1<<8)  ; XTIDE mod, Address lines 0 and 3 reversed
     43FLG_DPT_SERIAL_DEVICE           EQU (1<<9)  ; Serial Port Device
     44FLG_DPT_BLOCK_MODE_SUPPORTED    EQU (1<<10) ; Use block transfer commands
    6645
     46FLG_DPT_RESET_nDRDY             EQU (1<<12) ; Drive ready to accept commands
     47FLG_DPT_RESET_nINITPRMS         EQU (1<<13) ; Initialize Device Parameters successfull
     48FLG_DPT_RESET_nRECALIBRATE      EQU (1<<14) ; Recalibrate successfull
     49FLG_DPT_RESET_nSETBLOCK         EQU (1<<15) ; Initialize Block Mode successfull
     50MASK_DPT_RESET                  EQU 0F000h
    6751
    68 ; Extended DPT for EBIOS support.
    69 ; This struct cannot exist with PDPT (XTIDE Universal BIOS partitioned drive).
    70 struc EBDPT
    71     .dpt        resb    DPT_size
    72     .dwCapacity:
    73     .twCapacity resb    6   ; Total drive capacity in sectors
    74 endstruc
     52; Addressing modes for DPT.wFlags
     53ADDRESSING_MODE_FIELD_POSITION  EQU     5
     54ADDRESSING_MODE_LCHS            EQU     0   ; L-CHS Addressing Mode (NORMAL in many other BIOSes)
     55ADDRESSING_MODE_PCHS            EQU     1   ; P-CHS Addressing Mode (LARGE in many other BIOSes)
     56ADDRESSING_MODE_LBA28           EQU     2   ; 28-bit LBA Addressing Mode
     57ADDRESSING_MODE_LBA48           EQU     3   ; 48-bit LBA Addressing Mode
    7558
    7659
  • trunk/XTIDE_Universal_BIOS/Inc/IDE_8bit.inc

    r3 r150  
    1 ; File name     :   IDE_8bit.inc
    2 ; Project name  :   IDE BIOS
    3 ; Created date  :   4.4.2010
    4 ; Last update   :   13.4.2010
    5 ; Author        :   Tomi Tilli
     1; Project name  :   XTIDE Universal BIOS
    62; Description   :   Macros for accessing data port(s) on 8-bit
    73;                   IDE controllers.
    84%ifndef IDE_8BIT_INC
    95%define IDE_8BIT_INC
    10 
    11 ;--------------------------------------------------------------------
    12 ; Emulates REP INSW for XTIDE dual (8-bit) data port.
    13 ;
    14 ; eREP_DUAL_BYTE_PORT_INSW
    15 ;   Parameters:
    16 ;       CX:     Loop count
    17 ;       DX:     Port address (must be IDE Data Register)
    18 ;       ES:DI:  Ptr to destination buffer
    19 ;   Returns:
    20 ;       CX:     Zero
    21 ;       DI:     Incremented/decremented
    22 ;   Corrupts registers:
    23 ;       AX, FLAGS
    24 ;--------------------------------------------------------------------
    25 %macro eREP_DUAL_BYTE_PORT_INSW 0
    26     push    bx
    27     times 2 shr cx, 1           ; Loop unrolling
    28     mov     bx, 8               ; Bit mask for toggling data low/high reg
    29 ALIGN JUMP_ALIGN
    30 %%InswLoop:
    31     eDUAL_BYTE_PORT_INSW
    32     eDUAL_BYTE_PORT_INSW
    33     eDUAL_BYTE_PORT_INSW
    34     eDUAL_BYTE_PORT_INSW
    35     loop    %%InswLoop
    36     pop     bx
    37 %endmacro
    386
    397;--------------------------------------------------------------------
     
    6634%endmacro
    6735
    68 
    69 ;--------------------------------------------------------------------
    70 ; Emulates REP OUTSW for XTIDE dual (8-bit) data port.
    71 ;
    72 ; eREP_DUAL_BYTE_PORT_OUTSW
    73 ;   Parameters:
    74 ;       CX:     Loop count
    75 ;       DX:     Port address (must be IDE Data Register)
    76 ;       ES:SI:  Ptr to source buffer
    77 ;   Returns:
    78 ;       SI:     Incremented/decremented
    79 ;   Corrupts registers:
    80 ;       AX, CX
    81 ;--------------------------------------------------------------------
    82 %macro eREP_DUAL_BYTE_PORT_OUTSW 0
    83     push    ds
    84     push    bx
    85     times 2 shr cx, 1           ; Loop unrolling
    86     mov     bx, 8               ; Bit mask for toggling data low/high reg
    87     push    es                  ; Copy ES...
    88     pop     ds                  ; ...to DS
    89 ALIGN JUMP_ALIGN
    90 %%OutswLoop:
    91     eDUAL_BYTE_PORT_OUTSW
    92     eDUAL_BYTE_PORT_OUTSW
    93     eDUAL_BYTE_PORT_OUTSW
    94     eDUAL_BYTE_PORT_OUTSW
    95     loop    %%OutswLoop
    96     pop     bx
    97     pop     ds
    98 %endmacro
    9936
    10037;--------------------------------------------------------------------
     
    13067
    13168
    132 ;--------------------------------------------------------------------
    133 ; Emulates REP INSW for IDE controllers with single 8-bit Data Port.
    134 ;
    135 ; eREP_SINGLE_BYTE_PORT_INSW
    136 ;   Parameters:
    137 ;       CX:     Number of WORDs to transfer
    138 ;       DX:     IDE Data Port address
    139 ;       ES:DI:  Ptr to destination buffer
    140 ;   Returns:
    141 ;       DI:     Incremented/decremented
    142 ;   Corrupts registers:
    143 ;       AL, CX
    144 ;--------------------------------------------------------------------
    145 %macro eREP_SINGLE_BYTE_PORT_INSW 0
    146 %ifdef USE_186  ; INS instruction available
    147     shl     cx, 1               ; WORD count to BYTE count
    148     rep insb
    149 %else           ; If 8088/8086
    150     shr     cx, 1               ; WORD count to DWORD count
    151 ALIGN JUMP_ALIGN
    152 %%InsdLoop:
    153     in      al, dx
    154     stosb                       ; Store to [ES:DI]
    155     in      al, dx
    156     stosb
    157     in      al, dx
    158     stosb
    159     in      al, dx
    160     stosb
    161     loop    %%InsdLoop
    162 %endif
    163 %endmacro
    164 
    165 
    166 ;--------------------------------------------------------------------
    167 ; Emulates REP OUTSW for IDE controllers with single 8-bit Data Port.
    168 ;
    169 ; eREP_SINGLE_BYTE_PORT_OUTSW
    170 ;   Parameters:
    171 ;       CX:     Number of WORDs to transfer
    172 ;       DX:     IDE Data Port address
    173 ;       ES:SI:  Ptr to source buffer
    174 ;   Returns:
    175 ;       SI:     Incremented/decremented
    176 ;   Corrupts registers:
    177 ;       AL, CX
    178 ;--------------------------------------------------------------------
    179 %macro eREP_SINGLE_BYTE_PORT_OUTSW 0
    180 %ifdef USE_186  ; OUTS instruction available
    181     shl     cx, 1               ; WORD count to BYTE count
    182     eSEG    es                  ; Source is ES segment
    183     rep outsb
    184 %else           ; If 8088/8086
    185     shr     cx, 1               ; WORD count to DWORD count
    186     push    ds                  ; Store DS
    187     push    es                  ; Copy ES...
    188     pop     ds                  ; ...to DS
    189 ALIGN JUMP_ALIGN
    190 %%OutsdLoop:
    191     lodsb                       ; Load from [DS:SI] to AL
    192     out     dx, al
    193     lodsb
    194     out     dx, al
    195     lodsb
    196     out     dx, al
    197     lodsb
    198     out     dx, al
    199     loop    %%OutsdLoop
    200     pop     ds                  ; Restore DS
    201 %endif
    202 %endmacro
    203 
    204 
    20569%endif ; IDE_8BIT_INC
  • trunk/XTIDE_Universal_BIOS/Inc/IdeRegisters.inc

    r3 r150  
    1 ; File name     :   IdeRegisters.inc
    2 ; Project name  :   IDE BIOS
    3 ; Created date  :   23.3.2010
    4 ; Last update   :   23.3.2010
    5 ; Author        :   Tomi Tilli
     1; Project name  :   XTIDE Universal BIOS
    62; Description   :   Equates for IDE registers, flags and commands.
    73%ifndef IDEREGISTERS_INC
     
    95
    106; IDE Register offsets from Command Block base port
    11 REG_IDE_DATA            EQU     0       ; Data Register
    12 REGR_IDE_ERROR          EQU     1       ; Error Register
    13 REGW_IDE_FEAT           EQU     1       ; Features Register (ATA1+)
    14 ;REGW_IDE_WRPC          EQU     1       ; Write Precompensation Register (obsolete on ATA1+)
    15 REG_IDE_CNT             EQU     2       ; Sector Count Register
    16 REG_IDE_SECT            EQU     3       ; Sector Number Register (LBA 7...0)
    17 REG_IDE_LBA_LOW         EQU     3       ; LBA Low Register
    18 REG_IDE_LOCYL           EQU     4       ; Low Cylinder Register (LBA 15...8)
    19 REG_IDE_LBA_MID         EQU     4       ; LBA Mid Register
    20 REG_IDE_HICYL           EQU     5       ; High Cylinder Register (LBA 23...16)
    21 REG_IDE_LBA_HIGH        EQU     5       ; LBA High Register
    22 REG_IDE_DRVHD           EQU     6       ; Drive and Head Register (LBA 27...24)
    23 REGR_IDE_ST             EQU     7       ; Status Register
    24 REGW_IDE_CMD            EQU     7       ; Command Register
    25 REG_IDE_HIDATA          EQU     8       ; XTIDE Data High Register (actually first Control Block reg)
     7DATA_REGISTER                   EQU     0
     8ERROR_REGISTER_in               EQU     1       ; Read only
     9FEATURES_REGISTER_out           EQU     1       ; Write only, ATA1+
     10;WRITE_PRECOMPENSATION_out      EQU     1       ; Write only, Obsolete on ATA1+
     11SECTOR_COUNT_REGISTER           EQU     2
     12SECTOR_NUMBER_REGISTER          EQU     3       ; LBA Low Register
     13LOW_CYLINDER_REGISTER           EQU     4       ; LBA Middle Register
     14HIGH_CYLINDER_REGISTER          EQU     5       ; LBA High Register
     15LBA_LOW_REGISTER                EQU     3       ; LBA 7...0, LBA48 31...24
     16LBA_MIDDLE_REGISTER             EQU     4       ; LBA 15...8, LBA48 39...32
     17LBA_HIGH_REGISTER               EQU     5       ; LBA 23...16, LBA48 47...40
     18DRIVE_AND_HEAD_SELECT_REGISTER  EQU     6       ; LBA28 27...24
     19STATUS_REGISTER_in              EQU     7       ; Read only
     20COMMAND_REGISTER_out            EQU     7       ; Write only
     21XTIDE_DATA_HIGH_REGISTER        EQU     8       ; Non-standard (actually first Control Block reg)
    2622
    2723; IDE Register offsets from Control Block base port
    2824; (usually Command Block base port + 200h)
    29 REGR_IDEC_AST           EQU     6       ; Alternate Status Register
    30 REGW_IDEC_CTRL          EQU     6       ; Device Control Register
    31 ;REGR_IDEC_ADDR         EQU     7       ; Drive Address Register (obsolete on ATA2+)
     25ALTERNATE_STATUS_REGISTER_in    EQU     6       ; Read only
     26DEVICE_CONTROL_REGISTER_out     EQU     6       ; Write only
     27;DRIVE_ADDRESS_REGISTER         EQU     7       ; Obsolete on ATA2+
    3228
     29; Bit mask for XTIDE mod with reversed A0 and A3 address lines
     30MASK_A3_AND_A0_ADDRESS_LINES    EQU     ((1<<3) | (1<<0))
    3331
    3432; Bit definitions for IDE Error Register
    35 FLG_IDE_ERR_BBK         EQU     (1<<7)  ; Bad Block Detected (reserved on ATA2+, command dependent on ATA4+)
    36 FLG_IDE_ERR_UNC         EQU     (1<<6)  ; Uncorrectable Data Error (command dependent on ATA4+)
    37 FLG_IDE_ERR_MC          EQU     (1<<5)  ; Media Changed (command dependent on ATA4+)
    38 FLG_IDE_ERR_IDNF        EQU     (1<<4)  ; ID Not Found (command dependent on ATA4+)
    39 FLG_IDE_ERR_MCR         EQU     (1<<3)  ; Media Change Request (command dependent on ATA4+)
    40 FLG_IDE_ERR_ABRT        EQU     (1<<2)  ; Command Aborted
    41 FLG_IDE_ERR_TK0NF       EQU     (1<<1)  ; Track 0 Not Found (command dependent on ATA4+)
    42 FLG_IDE_ERR_AMNF        EQU     (1<<0)  ; Address Mark Not Found (command dependent on ATA4+)
     33FLG_ERROR_BBK           EQU     (1<<7)  ; Bad Block Detected (reserved on ATA2+, command dependent on ATA4+)
     34FLG_ERROR_UNC           EQU     (1<<6)  ; Uncorrectable Data Error (command dependent on ATA4+)
     35FLG_ERROR_MC            EQU     (1<<5)  ; Media Changed (command dependent on ATA4+)
     36FLG_ERROR_IDNF          EQU     (1<<4)  ; ID Not Found (command dependent on ATA4+)
     37FLG_ERROR_MCR           EQU     (1<<3)  ; Media Change Request (command dependent on ATA4+)
     38FLG_ERROR_ABRT          EQU     (1<<2)  ; Command Aborted
     39FLG_ERROR_TK0NF         EQU     (1<<1)  ; Track 0 Not Found (command dependent on ATA4+)
     40FLG_ERROR_AMNF          EQU     (1<<0)  ; Address Mark Not Found (command dependent on ATA4+)
    4341
    4442; Bit definitions for IDE Drive and Head Select Register
    45 FLG_IDE_DRVHD_LBA       EQU     (1<<6)  ; LBA Addressing enabled (instead of CHS)
    46 FLG_IDE_DRVHD_DRV       EQU     (1<<4)  ; Drive Select (0=Master, 1=Slave)
    47 MASK_IDE_DRVHD_HEAD     EQU     0Fh     ; Head select bits (bits 0...3)
    48 MASK_IDE_DRVHD_SET      EQU     0A0h    ; Bits that must be set to 1 on ATA1 (reserved on ATA2+)
     43FLG_DRVNHEAD_LBA        EQU     (1<<6)  ; LBA Addressing enabled (instead of CHS)
     44FLG_DRVNHEAD_DRV        EQU     (1<<4)  ; Drive Select (0=Master, 1=Slave)
     45MASK_DRVNHEAD_HEAD      EQU     0Fh     ; Head select bits (bits 0...3)
     46MASK_DRVNHEAD_SET       EQU     0A0h    ; Bits that must be set to 1 on ATA1 (reserved on ATA2+)
    4947
    5048; Bit definitions for IDE Status Register
    51 FLG_IDE_ST_BSY          EQU     (1<<7)  ; Busy (other flags undefined when set)
    52 FLG_IDE_ST_DRDY         EQU     (1<<6)  ; Device Ready
    53 FLG_IDE_ST_DF           EQU     (1<<5)  ; Device Fault (command dependent on ATA4+)
    54 FLG_IDE_ST_DSC          EQU     (1<<4)  ; Device Seek Complete (command dependent on ATA4+)
    55 FLG_IDE_ST_DRQ          EQU     (1<<3)  ; Data Request
    56 FLG_IDE_ST_CORR         EQU     (1<<2)  ; Corrected Data (obsolete on ATA4+)
    57 FLG_IDE_ST_IDX          EQU     (1<<1)  ; Index (vendor specific on ATA2+, obsolete on ATA4+)
    58 FLG_IDE_ST_ERR          EQU     (1<<0)  ; Error
     49FLG_STATUS_BSY          EQU     (1<<7)  ; Busy (other flags undefined when set)
     50FLG_STATUS_DRDY         EQU     (1<<6)  ; Device Ready
     51FLG_STATUS_DF           EQU     (1<<5)  ; Device Fault (command dependent on ATA4+)
     52FLG_STATUS_DSC          EQU     (1<<4)  ; Device Seek Complete (command dependent on ATA4+)
     53FLG_STATUS_DRQ          EQU     (1<<3)  ; Data Request
     54FLG_STATUS_CORR         EQU     (1<<2)  ; Corrected Data (obsolete on ATA4+)
     55FLG_STATUS_IDX          EQU     (1<<1)  ; Index (vendor specific on ATA2+, obsolete on ATA4+)
     56FLG_STATUS_ERR          EQU     (1<<0)  ; Error
    5957
    6058; Bit definitions for IDE Device Control Register
    6159; Bit 0 must be zero, unlisted bits are reserved.
    62 FLG_IDE_CTRL_O8H        EQU     (1<<3)  ; Drive has more than 8 heads (pre-ATA only, 1 on ATA1, reserved on ATA2+)
    63 FLG_IDE_CTRL_SRST       EQU     (1<<2)  ; Software Reset
    64 FLG_IDE_CTRL_nIEN       EQU     (1<<1)  ; Negated Interrupt Enable (IRQ disabled when set)
    65 
     60FLG_DEVCONTROL_HOB      EQU     (1<<7)  ; High Order Byte (ATA6+)
     61;FLG_DEVCONTROL_O8H     EQU     (1<<3)  ; Drive has more than 8 heads (pre-ATA only, 1 on ATA1, reserved on ATA2+)
     62FLG_DEVCONTROL_SRST     EQU     (1<<2)  ; Software Reset
     63FLG_DEVCONTROL_nIEN     EQU     (1<<1)  ; Negated Interrupt Enable (IRQ disabled when set)
    6664
    6765; Commands for IDE Controller
    68 ;HCMD_RECALIBRATE       EQU     10h     ; Recalibrate
    69 HCMD_READ_SECT          EQU     20h     ; Read Sectors (with retries)
    70 HCMD_WRITE_SECT         EQU     30h     ; Write Sectors (with retries)
    71 HCMD_VERIFY_SECT        EQU     40h     ; Read Verify Sectors (with retries)
    72 ;HCMD_FORMAT            EQU     50h     ; Format track
    73 HCMD_SEEK               EQU     70h     ; Seek
    74 ;HCMD_DIAGNOSTIC        EQU     90h     ; Execute Device Diagnostic
    75 HCMD_INIT_DEV           EQU     91h     ; Initialize Device Parameters
    76 HCMD_READ_MUL           EQU     0C4h    ; Read Multiple (=block)
    77 HCMD_WRITE_MUL          EQU     0C5h    ; Write Multiple (=block)
    78 HCMD_SET_MUL            EQU     0C6h    ; Set Multiple Mode (=block size)
    79 HCMD_ID_DEV             EQU     0ECh    ; Identify Device
    80 HCMD_SET_FEAT           EQU     0EFh    ; Set Features
    81 
    82 ; Set Features subcommands
    83 HFEAT_SET_XFER_MODE     EQU     03h     ; Set transfer mode based on value in Sector Count register
     66COMMAND_READ_SECTORS                    EQU     20h
     67COMMAND_READ_SECTORS_EXT                EQU     24h     ; LBA48
     68COMMAND_WRITE_SECTORS                   EQU     30h
     69COMMAND_WRITE_SECTORS_EXT               EQU     34h     ; LBA48
     70COMMAND_VERIFY_SECTORS                  EQU     40h
     71COMMAND_VERIFY_SECTORS_EXT              EQU     42h     ; LBA48
     72COMMAND_SEEK                            EQU     70h
     73COMMAND_INITIALIZE_DEVICE_PARAMETERS    EQU     91h
     74COMMAND_SET_MULTIPLE_MODE               EQU     0C6h    ; Block mode
     75COMMAND_READ_MULTIPLE                   EQU     0C4h    ; Block mode
     76COMMAND_READ_MULTIPLE_EXT               EQU     29h     ; LBA48, Block mode
     77COMMAND_WRITE_MULTIPLE                  EQU     0C5h    ; Block mode
     78COMMAND_WRITE_MULTIPLE_EXT              EQU     39h     ; LBA48, Block mode
     79COMMAND_IDENTIFY_DEVICE                 EQU     0ECh
     80COMMAND_SET_FEATURES                    EQU     0EFh
    8481
    8582
  • trunk/XTIDE_Universal_BIOS/Inc/Int13h.inc

    r28 r150  
    1 ; File name     :   Int13h.inc
    2 ; Project name  :   IDE BIOS
    3 ; Created date  :   23.3.2010
    4 ; Last update   :   29.7.2010
    5 ; Author        :   Tomi Tilli
     1; Project name  :   XTIDE Universal BIOS
    62; Description   :   Equates used in INT 13h functions.
    73%ifndef INT13H_INC
     
    4036
    4137
    42 ; Timeout values for IDE controller timeout
    43 ; 255 is the maximum value. Zero means immediate timeout.
    44 B_TIMEOUT_BSY           EQU     (1000/55)   ; 1000 ms
    45 B_TIMEOUT_RDY           EQU     (1000/55)   ; 1000 ms
    46 B_TIMEOUT_DRQ           EQU     255         ;   14 s (some CF cards occasionally have long write delays)
    47 B_TIMEOUT_DRVINFO       EQU     (500/55)    ;  500 ms
    48 B_TIMEOUT_RESET         EQU     255         ;   14 s
    49 
    50 
    51 
    5238; Floppy Drive types returned by INT 13h, AH=08h
    5339FLOPPY_TYPE_525_OR_35_DD    EQU 0
     
    5945
    6046
     47MAX_SUPPORTED_BLOCK_SIZE_IN_SECTORS     EQU     64
     48
     49%define TIMEOUT_AND_STATUS_TO_WAIT(timeout, status)     (((timeout)<<8) | (status))
     50
     51
    6152%endif ; INT13H_INC
  • trunk/XTIDE_Universal_BIOS/Inc/RamVars.inc

    r148 r150  
    55
    66; Segment when RAMVARS is stored to top of interrupt vectors.
    7 SEGMENT_RAMVARS_TOP_OF_INTERRUPT_VECTORS        EQU     30h
     7LITE_MODE_RAMVARS_SEGMENT   EQU     30h
    88
    99
     
    2121struc RAMVARS
    2222    .fpOldI13h          resb    4   ; Far pointer to old INT 13h handler
    23     .wIdeBase           resb    2   ; Base port address for currently handled controller
    2423    .wTimeoutCounter    resb    2
     24    .pInServiceDPT      resb    2   ; Ptr to DPT for drive waiting for interrupt
     25    .wSignature         resb    2   ; Sign for finding stolen 1 kiB
    2526
    2627    .wDrvCntAndFirst:
     
    3233endstruc
    3334
    34 ; Full mode RAM variables.
    35 struc FULLRAMVARS
    36     .ramVars            resb    RAMVARS_size
    37     .wSign              resb    2       ; FULLRAMVARS signature for finding segment
     35RAMVARS_SIGNATURE       EQU "Xu"    ; RAMVARS signature for .wSignature
     36
     37
     38struc IDEPACK
     39    .bDrvAndHead            resb    1   ; LBA28 27...24
     40    .bFeatures              resb    1
     41
     42    .wSectorCountAndLbaLow:
     43    .bSectorCount           resb    1
     44    .bSectorNumber:
     45    .bLbaLow                resb    1   ; LBA 7...0
     46
     47    .wCylinder:
     48    .wLbaMiddleAndHigh:
     49    .bLbaMiddle             resb    1   ; LBA 15...8
     50    .bLbaHigh               resb    1   ; LBA 23...16
     51
     52    .bCommand               resb    1
     53    .bDeviceControl         resb    1   ; Offset 7 shared with PIOVARS
     54
     55    ; Parameters for 48-bit LBA
     56    .wSectorCountHighAndLbaLowExt:
     57    .bSectorCountHighExt    resb    1   ; LBA48 Sector Count 15...8
     58    .bLbaLowExt             resb    1   ; LBA48 31...24
     59
     60    .wLbaMiddleAndHighExt:
     61    .bLbaMiddleExt          resb    1   ; LBA48 39...32
     62    .bLbaHighExt            resb    1   ; LBA48 47...40
     63
     64    .intpack                resb    INTPACK_size
    3865endstruc
    3966
    40 W_SIGN_FULLRAMVARS      EQU "fR"        ; FULLRAMVARS signature
     67EXTRA_WORDS_TO_RESERVE_FOR_INTPACK  EQU ((IDEPACK_size - INTPACK_size) / 2)
    4168
    4269
  • trunk/XTIDE_Universal_BIOS/Inc/RomVars.inc

    r143 r150  
    4141    .wPort              resb    2   ; IDE Base Port for Command Block (usual) Registers
    4242    .wPortCtrl          resb    2   ; IDE Base Port for Control Block Registers
    43     .bBusType           resb    1   ; Bus type
     43    .bDevice            resb    1   ; Device type
    4444    .bIRQ               resb    1   ; Interrupt Request Number
    4545    .drvParamsMaster    resb    DRVPARAMS_size
     
    4747endstruc
    4848
    49 ; Bus types for IDEVARS.bBusType
    50 BUS_TYPE_8_DUAL         EQU (0<<1)  ; XTIDE transfers with two 8-bit data ports
    51 BUS_TYPE_16             EQU (1<<1)  ; Normal 16-bit AT-IDE transfers
    52 BUS_TYPE_32             EQU (2<<1)  ; 32-bit VLB and PCI transfers
    53 BUS_TYPE_8_SINGLE       EQU (3<<1)  ; 8-bit transfers with single 8-bit data port
     49; Device types for IDEVARS.bDeviceType
     50DEVICE_8BIT_DUAL_PORT_XTIDE             EQU (0<<1)
     51DEVICE_XTIDE_WITH_REVERSED_A3_AND_A0    EQU (1<<1)
     52DEVICE_8BIT_SINGLE_PORT                 EQU (2<<1)
     53DEVICE_16BIT_ATA                        EQU (3<<1)
     54DEVICE_32BIT_ATA                        EQU (4<<1)
     55DEVICE_SERIAL_PORT                      EQU (5<<1)
    5456
    5557
Note: See TracChangeset for help on using the changeset viewer.