Changeset 150 in xtideuniversalbios


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
Files:
15 added
7 deleted
36 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
  • trunk/XTIDE_Universal_BIOS/Src/Boot/BootMenuPrint.asm

    r135 r150  
    111111BootMenuPrint_HardDiskMenuitem:
    112112    call    PrintDriveNumberAfterTranslationFromDL
    113     call    FindDPT_ForDriveNumber      ; DS:DI to point DPT
     113    call    RamVars_IsDriveHandledByThisBIOS
    114114    jnc     SHORT .HardDiskMenuitemForForeignDrive
    115115    ; Fall to .HardDiskMenuitemForOurDrive
     
    280280ALIGN JUMP_ALIGN
    281281BootMenuPrint_HardDiskMenuitemInformation:
     282    call    RamVars_IsDriveHandledByThisBIOS
     283    jnc     SHORT .HardDiskMenuitemInfoForForeignDrive
    282284    call    FindDPT_ForDriveNumber      ; DS:DI to point DPT
    283     jnc     SHORT .HardDiskMenuitemInfoForForeignDrive
    284285    ; Fall to .HardDiskMenuitemInfoForOurDrive
    285286
     
    303304
    304305    ; Get and push L-CHS size
    305     call    HCapacity_GetSectorCountFromOurAH08h
     306    mov     [RAMVARS.wTimeoutCounter], dl       ; Store drive number
     307    call    AH15h_GetSectorCountToDXAX
    306308    call    ConvertSectorCountInBXDXAXtoSizeAndPushForFormat
    307309
    308310    ; Get and push total LBA size
    309     mov     dl, [di+DPT.bDrvNum]
     311    mov     dl, [RAMVARS.wTimeoutCounter]       ; Restore drive number
    310312    call    BootInfo_GetTotalSectorCount
    311313    call    ConvertSectorCountInBXDXAXtoSizeAndPushForFormat
     
    332334
    333335    call    DriveXlate_ToOrBack
    334     call    HCapacity_GetSectorCountFromForeignAH08h
     336    call    AH15h_GetSectorCountFromForeignDriveToDXAX
    335337    call    ConvertSectorCountInBXDXAXtoSizeAndPushForFormat
    336338
  • trunk/XTIDE_Universal_BIOS/Src/Boot/BootMenuPrintCfg.asm

    r127 r150  
    1717;       Nothing
    1818;   Corrupts registers:
    19 ;       AX, BX, CX, DX, SI, DI, ES
     19;       AX, BX, CX, DX, SI, DI
    2020;--------------------------------------------------------------------
    2121ALIGN JUMP_ALIGN
     
    2424    mov     si, g_szCfgHeader
    2525    call    BootMenuPrint_NullTerminatedStringFromCSSIandSetCF
    26     call    BootMenuPrintCfg_GetPointers
     26    eMOVZX  ax, BYTE [di+DPT.bIdevarsOffset]
     27    xchg    si, ax                      ; CS:SI now points to IDEVARS
    2728    ; Fall to PushAndFormatCfgString
    28 
    2929
    3030;--------------------------------------------------------------------
     
    3232;   Parameters:
    3333;       DS:DI:  Ptr to DPT
    34 ;       ES:BX:  Ptr to BOOTNFO
    3534;       CS:SI:  Ptr to IDEVARS
    3635;   Returns:
     
    4847;   Parameters:
    4948;       DS:DI:  Ptr to DPT
    50 ;       ES:BX:  Ptr to BOOTNFO
    5149;       CS:SI:  Ptr to IDEVARS
    5250;   Returns:
     
    5654;--------------------------------------------------------------------
    5755PushAddressingMode:
    58     xchg    ax, bx
    59     mov     bx, MASK_DPT_ADDR   ; Load addressing mode mask
    60     and     bl, [di+DPT.bFlags] ; Addressing mode now in BX
    61     push    WORD [cs:bx+.rgszAddressingModeString]
    62     xchg    bx, ax
    63     jmp     SHORT .NextPush
    64 ALIGN WORD_ALIGN
    65 .rgszAddressingModeString:
    66     dw      g_szLCHS
    67     dw      g_szPCHS
    68     dw      g_szLBA28
    69     dw      g_szLBA48
    70 ALIGN JUMP_ALIGN
    71 .NextPush:
     56    call    AccessDPT_GetAddressingModeForWordLookToBX
     57    push    WORD [cs:bx+rgszAddressingModeString]
    7258
    7359;--------------------------------------------------------------------
     
    7561;   Parameters:
    7662;       DS:DI:  Ptr to DPT
    77 ;       ES:BX:  Ptr to BOOTNFO
    7863;       CS:SI:  Ptr to IDEVARS
    7964;   Returns:
     
    8368;--------------------------------------------------------------------
    8469PushBlockMode:
    85     eMOVZX  ax, BYTE [di+DPT.bSetBlock]
     70    mov     ax, 1
     71    test    WORD [di+DPT.wFlags], FLG_DPT_BLOCK_MODE_SUPPORTED
     72    jz      SHORT .PushBlockSizeFromAX
     73    mov     al, [di+DPT_ATA.bSetBlock]
     74.PushBlockSizeFromAX:
    8675    push    ax
    8776
     
    9079;   Parameters:
    9180;       DS:DI:  Ptr to DPT
    92 ;       ES:BX:  Ptr to BOOTNFO
    9381;       CS:SI:  Ptr to IDEVARS
    9482;   Returns:
     
    9987PushBusType:
    10088    xchg    ax, bx      ; Store BX to AX
    101     eMOVZX  bx, BYTE [cs:si+IDEVARS.bBusType]
    102     mov     bx, [cs:bx+.rgwBusTypeValues]   ; Char to BL, Int to BH
     89    eMOVZX  bx, BYTE [cs:si+IDEVARS.bDevice]
     90    mov     bx, [cs:bx+rgwBusTypeValues]    ; Char to BL, Int to BH
    10391    eMOVZX  dx, bh
    10492    push    bx          ; Push character
    105     push    dx          ; Push 8, 16 or 32
     93    push    dx          ; Push 1, 8, 16 or 32
    10694    xchg    bx, ax      ; Restore BX
    107     jmp     SHORT .NextPush
    108 ALIGN WORD_ALIGN
    109 .rgwBusTypeValues:
    110     db      'D', 8      ; BUS_TYPE_8_DUAL
    111     db      ' ', 16     ; BUS_TYPE_16
    112     db      ' ', 32     ; BUS_TYPE_32
    113     db      'S', 8      ; BUS_TYPE_8_SINGLE
    114 ALIGN JUMP_ALIGN
    115 .NextPush:
    11695
    11796;--------------------------------------------------------------------
     
    11998;   Parameters:
    12099;       DS:DI:  Ptr to DPT
    121 ;       ES:BX:  Ptr to BOOTNFO
    122100;       CS:SI:  Ptr to IDEVARS
    123101;   Returns:
     
    152130;   Parameters:
    153131;       DS:DI:  Ptr to DPT
    154 ;       ES:BX:  Ptr to BOOTNFO
    155132;       CS:SI:  Ptr to IDEVARS
    156133;   Returns:
     
    160137;--------------------------------------------------------------------
    161138PushResetStatus:
    162     eMOVZX  ax, BYTE [di+DPT.bReset]
     139    mov     ax, [di+DPT.wFlags]
     140    and     ax, MASK_DPT_RESET
    163141    push    ax
    164142
     
    177155
    178156
    179 ;--------------------------------------------------------------------
    180 ; BootMenuPrintCfg_GetPointers
    181 ;   Parameters:
    182 ;       DS:DI:  Ptr to DPT
    183 ;   Returns:
    184 ;       DS:DI:  Ptr to DPT
    185 ;       ES:BX:  Ptr to BOOTNFO
    186 ;       CS:SI:  Ptr to IDEVARS
    187 ;   Corrupts registers:
    188 ;       AX, DL
    189 ;--------------------------------------------------------------------
    190 ALIGN JUMP_ALIGN
    191 BootMenuPrintCfg_GetPointers:
    192     mov     dl, [di+DPT.bDrvNum]        ; Load Drive number to DL
    193     call    BootInfo_GetOffsetToBX      ; ES:BX now points...
    194     LOAD_BDA_SEGMENT_TO es, ax, !       ; ...to BOOTNFO
    195     mov     al, [di+DPT.bIdeOff]
    196     xchg    si, ax                      ; CS:SI now points to IDEVARS
    197     ret
     157ALIGN WORD_ALIGN
     158rgszAddressingModeString:
     159    dw      g_szLCHS
     160    dw      g_szPCHS
     161    dw      g_szLBA28
     162    dw      g_szLBA48
     163
     164rgwBusTypeValues:
     165    db      'D', 8      ; DEVICE_8BIT_DUAL_PORT_XTIDE
     166    db      'X', 8      ; DEVICE_XTIDE_WITH_REVERSED_A3_AND_A0
     167    db      'S', 8      ; DEVICE_8BIT_SINGLE_PORT
     168    db      ' ', 16     ; DEVICE_16BIT_ATA
     169    db      ' ', 32     ; DEVICE_32BIT_ATA
     170    db      ' ', 1      ; DEVICE_SERIAL_PORT
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h.asm

    r148 r150  
    2222Int13h_DiskFunctionsHandler:
    2323    sti                                 ; Enable interrupts
    24     SAVE_AND_GET_INTPACK_TO_SSBP
     24    cld                                 ; String instructions to increment pointers
     25    SAVE_AND_GET_INTPACK_WITH_EXTRA_WORDS_TO_SSBP EXTRA_WORDS_TO_RESERVE_FOR_INTPACK
    2526
    2627    call    RamVars_GetSegmentToDS
     
    4647;       DL:     Translated drive number
    4748;       DS:     RAMVARS segment
    48 ;       SS:BP:  Ptr to INTPACK
     49;       SS:BP:  Ptr to IDEPACK
    4950;       BX, DI: Corrupted on Int13h_DiskFunctionsHandler
    5051;       Other:  Function specific INT 13h parameters
     
    5859Int13h_DirectCallToAnotherBios:
    5960    call    ExchangeCurrentInt13hHandlerWithOldInt13hHandler
    60     mov     bx, [bp+INTPACK.bx]
    61     mov     di, [bp+INTPACK.di]
    62     mov     ds, [bp+INTPACK.ds]
    63     push    WORD [bp+INTPACK.flags]
     61    mov     bx, [bp+IDEPACK.intpack+INTPACK.bx]
     62    mov     di, [bp+IDEPACK.intpack+INTPACK.di]
     63    mov     ds, [bp+IDEPACK.intpack+INTPACK.ds]
     64    push    WORD [bp+IDEPACK.intpack+INTPACK.flags]
    6465    popf
    6566    push    bp
    66     mov     bp, [bp+INTPACK.bp]
     67    mov     bp, [bp+IDEPACK.intpack+INTPACK.bp]
    6768    int     BIOS_DISK_INTERRUPT_13h ; Can safely do as much recursion as it wants
    6869
     
    7071    pop     bp  ; Standard INT 13h functions never uses BP as return register
    7172%ifdef USE_386
    72     mov     [bp+INTPACK.gs], gs
    73     mov     [bp+INTPACK.fs], fs
     73    mov     [bp+IDEPACK.intpack+INTPACK.gs], gs
     74    mov     [bp+IDEPACK.intpack+INTPACK.fs], fs
    7475%endif
    75     mov     [bp+INTPACK.es], es
    76     mov     [bp+INTPACK.ds], ds
    77     mov     [bp+INTPACK.di], di
    78     mov     [bp+INTPACK.si], si
    79     mov     [bp+INTPACK.bx], bx
    80     mov     [bp+INTPACK.dh], dh
    81     mov     [bp+INTPACK.cx], cx
    82     mov     [bp+INTPACK.ax], ax
     76    mov     [bp+IDEPACK.intpack+INTPACK.es], es
     77    mov     [bp+IDEPACK.intpack+INTPACK.ds], ds
     78    mov     [bp+IDEPACK.intpack+INTPACK.di], di
     79    mov     [bp+IDEPACK.intpack+INTPACK.si], si
     80    mov     [bp+IDEPACK.intpack+INTPACK.bx], bx
     81    mov     [bp+IDEPACK.intpack+INTPACK.dh], dh
     82    mov     [bp+IDEPACK.intpack+INTPACK.cx], cx
     83    mov     [bp+IDEPACK.intpack+INTPACK.ax], ax
    8384    pushf
    84     pop     WORD [bp+INTPACK.flags]
     85    pop     WORD [bp+IDEPACK.intpack+INTPACK.flags]
    8586    call    RamVars_GetSegmentToDS
    8687    cmp     dl, [RAMVARS.xlateVars+XLATEVARS.bXlatedDrv]
    8788    je      SHORT .ExchangeInt13hHandlers
    88     mov     [bp+INTPACK.dl], dl     ; Something is returned in DL
     89    mov     [bp+IDEPACK.intpack+INTPACK.dl], dl     ; Something is returned in DL
    8990ALIGN JUMP_ALIGN
    9091.ExchangeInt13hHandlers:
     
    9899;   Parameters:
    99100;       AH:     BIOS Error code
    100 ;       SS:BP:  Ptr to INTPACK
     101;       SS:BP:  Ptr to IDEPACK
    101102;   Returns:
    102103;       All registers are loaded from INTPACK
     
    104105ALIGN JUMP_ALIGN
    105106Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH:
    106     call    HError_SetErrorCodeToBdaAndToIntpackInSSBPfromAH
     107    call    Int13h_SetErrorCodeToBdaAndToIntpackInSSBPfromAH
    107108Int13h_ReturnFromHandlerWithoutStoringErrorCode:
    108     or      WORD [bp+INTPACK.flags], FLG_FLAGS_IF   ; Return with interrupts enabled
     109    or      WORD [bp+IDEPACK.intpack+INTPACK.flags], FLG_FLAGS_IF   ; Return with interrupts enabled
    109110    mov     sp, bp                                  ; Now we can exit anytime
    110     RESTORE_INTPACK_FROM_SSBP
     111    RESTORE_INTPACK_WITH_EXTRA_WORDS_FROM_SSBP EXTRA_WORDS_TO_RESERVE_FOR_INTPACK
    111112
    112113
     
    146147    LOAD_BDA_SEGMENT_TO es, di
    147148    mov     di, [RAMVARS.fpOldI13h]
     149    cli
    148150    xchg    di, [es:BIOS_DISK_INTERRUPT_13h*4]
    149151    mov     [RAMVARS.fpOldI13h], di
     
    152154    mov     [RAMVARS.fpOldI13h+2], di
    153155    pop     es
     156    sti
     157    ret
     158
     159
     160;--------------------------------------------------------------------
     161; Int13h_SetErrorCodeToBdaAndToIntpackInSSBPfromAH
     162; Int13h_SetErrorCodeToIntpackInSSBPfromAH
     163;   Parameters:
     164;       AH:     BIOS error code (00h = no error)
     165;       SS:BP:  Ptr to IDEPACK
     166;   Returns:
     167;       SS:BP:  Ptr to IDEPACK with error condition set
     168;   Corrupts registers:
     169;       DS, DI
     170;--------------------------------------------------------------------
     171ALIGN JUMP_ALIGN
     172Int13h_SetErrorCodeToBdaAndToIntpackInSSBPfromAH:
     173    ; Store error code to BDA
     174    LOAD_BDA_SEGMENT_TO ds, di
     175    mov     [BDA.bHDLastSt], ah
     176
     177    ; Store error code to INTPACK
     178Int13h_SetErrorCodeToIntpackInSSBPfromAH:
     179    mov     [bp+IDEPACK.intpack+INTPACK.ah], ah
     180    test    ah, ah
     181    jnz     SHORT .SetCFtoIntpack
     182    and     BYTE [bp+IDEPACK.intpack+INTPACK.flags], ~FLG_FLAGS_CF
     183    ret
     184.SetCFtoIntpack:
     185    or      BYTE [bp+IDEPACK.intpack+INTPACK.flags], FLG_FLAGS_CF
    154186    ret
    155187
     
    224256;   dw  Int13h_UnsupportedFunction                      ; 3Fh,
    225257;   dw  Int13h_UnsupportedFunction                      ; 40h,
    226 ;   dw  Int13h_UnsupportedFunction                      ; 41h, Check if Extensions Present (EBIOS)
    227 ;   dw  Int13h_UnsupportedFunction                      ; 42h, Extended Read Sectors (EBIOS)
    228 ;   dw  Int13h_UnsupportedFunction                      ; 43h, Extended Write Sectors (EBIOS)
    229 ;   dw  Int13h_UnsupportedFunction                      ; 44h, Extended Verify Sectors (EBIOS)
    230 ;   dw  Int13h_UnsupportedFunction                      ; 45h, Lock and Unlock Drive (EBIOS)
    231 ;   dw  Int13h_UnsupportedFunction                      ; 46h, Eject Media Request (EBIOS)
    232 ;   dw  Int13h_UnsupportedFunction                      ; 47h, Extended Seek (EBIOS)
    233 ;   dw  Int13h_UnsupportedFunction                      ; 48h, Get Extended Drive Parameters (EBIOS)
    234 ;   dw  Int13h_UnsupportedFunction                      ; 49h, Get Extended Disk Change Status (EBIOS)
     258;   dw  Int13h_UnsupportedFunction                      ; 41h, Check if Extensions Present (EBIOS)*
     259;   dw  Int13h_UnsupportedFunction                      ; 42h, Extended Read Sectors (EBIOS)*
     260;   dw  Int13h_UnsupportedFunction                      ; 43h, Extended Write Sectors (EBIOS)*
     261;   dw  Int13h_UnsupportedFunction                      ; 44h, Extended Verify Sectors (EBIOS)*
     262;   dw  Int13h_UnsupportedFunction                      ; 45h, Lock and Unlock Drive (EBIOS)***
     263;   dw  Int13h_UnsupportedFunction                      ; 46h, Eject Media Request (EBIOS)***
     264;   dw  Int13h_UnsupportedFunction                      ; 47h, Extended Seek (EBIOS)*
     265;   dw  Int13h_UnsupportedFunction                      ; 48h, Get Extended Drive Parameters (EBIOS)*
     266;   dw  Int13h_UnsupportedFunction                      ; 49h, Get Extended Disk Change Status (EBIOS)***
    235267;   dw  Int13h_UnsupportedFunction                      ; 4Ah, Initiate Disk Emulation (Bootable CD-ROM)
    236268;   dw  Int13h_UnsupportedFunction                      ; 4Bh, Terminate Disk Emulation (Bootable CD-ROM)
    237269;   dw  Int13h_UnsupportedFunction                      ; 4Ch, Initiate Disk Emulation and Boot (Bootable CD-ROM)
    238270;   dw  Int13h_UnsupportedFunction                      ; 4Dh, Return Boot Catalog (Bootable CD-ROM)
    239 ;   dw  Int13h_UnsupportedFunction                      ; 4Eh, Set Hardware Configuration (EBIOS)
     271;   dw  Int13h_UnsupportedFunction                      ; 4Eh, Set Hardware Configuration (EBIOS)**
     272;
     273;   * = Enhanced Drive Access Support (minimum required EBIOS functions)
     274;  ** = Enhanced Disk Drive (EDD) Support
     275; *** = Drive Locking and Ejecting Support
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH0h_HReset.asm

    r148 r150  
    1313;               If bit 7 is set all hard disks and floppy disks reset.
    1414;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    15 ;       SS:BP:  Ptr to INTPACK
    16 ;   Returns with INTPACK in SS:BP:
     15;       SS:BP:  Ptr to IDEPACK
     16;   Returns with INTPACK:
    1717;       AH:     Int 13h return status (from drive requested in DL)
    1818;       CF:     0 if succesfull, 1 if error
     
    8989
    9090;--------------------------------------------------------------------
    91 ; ResetHardDisksHandledByOurBIOS
     91; AH0h_ResetHardDisksHandledByOurBIOS
    9292;   Parameters:
    9393;       BL:     Requested drive (DL when entering AH=00h)
    9494;       DS:     RAMVARS segment
     95;       SS:BP:  Ptr to IDEPACK
    9596;   Returns:
    9697;       BH:     Error code from requested drive (if available)
    9798;   Corrupts registers:
    98 ;       AX, CX, DX, DI
     99;       AX, CX, DX, SI, DI
    99100;--------------------------------------------------------------------
    100101ALIGN JUMP_ALIGN
     
    103104    test    dh, dh
    104105    jz      SHORT .AllDrivesReset       ; Return if no drives
    105     mov     dl, [RAMVARS.bFirstDrv]     ; Load number of first our drive
     106    mov     dl, [RAMVARS.bFirstDrv]     ; Load number of our first drive
    106107    add     dh, dl                      ; DH = one past last drive to reset
    107108ALIGN JUMP_ALIGN
     
    132133.BackupErrorCodeFromMasterOrSlaveToBH:
    133134    call    BackupErrorCodeFromTheRequestedDriveToBH
    134     mov     cx, [RAMVARS.wIdeBase]      ; Load base port for resetted drive
    135 
     135    call    GetBasePortToCX             ; Load base port for resetted drive
     136    push    cx
    136137    inc     dx                          ; DL to next drive
    137     call    FindDPT_ForDriveNumber      ; Get DPT to DS:DI, store port to RAMVARS
    138     jnc     SHORT .NoMoreDrivesOrNoSlaveDrive
    139     cmp     cx, [RAMVARS.wIdeBase]      ; Next drive is from same controller?
     138    call    GetBasePortToCX
     139    pop     di
     140    cmp     cx, di                      ; Next drive is from same controller?
    140141    je      SHORT BackupErrorCodeFromTheRequestedDriveToBH
    141142.NoMoreDrivesOrNoSlaveDrive:
    142143    dec     dx
     144    ret
     145
     146;--------------------------------------------------------------------
     147; GetBasePortToCX
     148;   Parameters:
     149;       DL:     Drive number
     150;       DS:     RAMVARS segment
     151;   Returns:
     152;       CX:     Base port address
     153;       CF:     Set if valid drive number
     154;               Cleared if invalid drive number
     155;   Corrupts registers:
     156;       DI
     157;--------------------------------------------------------------------
     158ALIGN JUMP_ALIGN
     159GetBasePortToCX:
     160    xchg    cx, bx
     161    xor     bx, bx
     162    call    FindDPT_ForDriveNumber
     163    jnc     SHORT .DptNotFound
     164    mov     bl, [di+DPT.bIdevarsOffset]
     165    mov     bx, [cs:bx+IDEVARS.wPort]
     166.DptNotFound:
     167    xchg    bx, cx
    143168    ret
    144169
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH10h_HReady.asm

    r148 r150  
    1212;       DL:     Translated Drive number
    1313;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    14 ;       SS:BP:  Ptr to INTPACK
    15 ;   Returns with INTPACK in SS:BP:
     14;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
     15;   Returns with INTPACK:
    1616;       AH:     Int 13h return status
    1717;       CF:     0 if succesfull, 1 if error
     
    1919ALIGN JUMP_ALIGN
    2020AH10h_HandlerForCheckDriveReady:
    21     call    HStatus_WaitRdyDefTime
    22     xor     ah, ah
     21%ifdef USE_186
     22    push    Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     23    jmp     Device_SelectDrive
     24%else
     25    call    Device_SelectDrive
    2326    jmp     Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     27%endif
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH11h_HRecal.asm

    r148 r150  
    1212;       DL:     Translated Drive number
    1313;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    14 ;       SS:BP:  Ptr to INTPACK
    15 ;   Returns with INTPACK in SS:BP:
     14;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
     15;   Returns with INTPACK:
    1616;       AH:     BIOS Error code
    1717;       CF:     0 if succesfull, 1 if error
     
    3232;   Parameters:
    3333;       DS:DI:  Ptr to DPT (in RAMVARS segment)
     34;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
    3435;   Returns:
    3536;       AH:     BIOS Error code
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH15h_HSize.asm

    r148 r150  
    1212;       DL:     Translated Drive number
    1313;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    14 ;       SS:BP:  Ptr to INTPACK
    15 ;   Returns with INTPACK in SS:BP:
     14;       SS:BP:  Ptr to IDEPACK
     15;   Returns with INTPACK:
    1616;       If succesfull:
    1717;           AH:     3 (Hard disk accessible)
     
    2525ALIGN JUMP_ALIGN
    2626AH15h_HandlerForReadDiskDriveSize:
    27     call    HCapacity_GetSectorCountFromOurAH08h        ; Sector count to DX:AX
    28     mov     [bp+INTPACK.cx], dx                         ; HIWORD to CX
    29     mov     [bp+INTPACK.dx], ax                         ; LOWORD to DX
     27    call    AH15h_GetSectorCountToDXAX
     28    mov     [bp+IDEPACK.intpack+INTPACK.cx], dx         ; HIWORD to CX
     29    mov     [bp+IDEPACK.intpack+INTPACK.dx], ax         ; LOWORD to DX
    3030
    3131    xor     ah, ah
    32     call    HError_SetErrorCodeToIntpackInSSBPfromAH    ; Store success to BDA and CF
    33     mov     BYTE [bp+INTPACK.ah], 3                     ; Type code = Hard disk
     32    call    Int13h_SetErrorCodeToIntpackInSSBPfromAH    ; Store success to BDA and CF
     33    mov     BYTE [bp+IDEPACK.intpack+INTPACK.ah], 3     ; Type code = Hard disk
    3434    jmp     Int13h_ReturnFromHandlerWithoutStoringErrorCode
     35
     36
     37;--------------------------------------------------------------------
     38; AH15h_GetSectorCountFromForeignDriveToDXAX:
     39; AH15h_GetSectorCountToDXAX:
     40;   Parameters:
     41;       DL:     Drive number
     42;       DS:     RAMVARS segment
     43;       DS:DI:  Ptr to DPT (AH15h_GetSectorCount only)
     44;   Returns:
     45;       DX:AX:  Total sector count
     46;       BX:     Zero
     47;   Corrupts registers:
     48;       CX
     49;--------------------------------------------------------------------
     50AH15h_GetSectorCountFromForeignDriveToDXAX:
     51    mov     ah, GET_DRIVE_PARAMETERS
     52    call    Int13h_CallPreviousInt13hHandler
     53    jmp     SHORT ConvertAH08hReturnValuesToSectorCount
     54
     55ALIGN JUMP_ALIGN
     56AH15h_GetSectorCountToDXAX:
     57    call    AH8h_GetDriveParameters
     58    ; Fall to ConvertAH08hReturnValuesToSectorCount
     59
     60ConvertAH08hReturnValuesToSectorCount:
     61    call    HAddress_ExtractLCHSparametersFromOldInt13hAddress
     62    xor     ax, ax          ; Zero AX
     63    inc     cx              ; Max cylinder number to cylinder count
     64    xchg    al, bh          ; AX=Max head number, BX=Sectors per track
     65    inc     ax              ; AX=Head count
     66    mul     bx              ; AX=Head count * Sectors per track
     67    mul     cx              ; DX:AX = Total sector count
     68    xor     bx, bx          ; Zero BX for 48-bit sector count (and clear CF)
     69    ret
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH1h_HStatus.asm

    r148 r150  
    1212;       DL:     Translated Drive number
    1313;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    14 ;       SS:BP:  Ptr to INTPACK
    15 ;   Returns with INTPACK in SS:BP:
     14;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
     15;   Returns with INTPACK:
    1616;       AH:     Int 13h floppy return status
    1717;       CF:     0 if AH = RET_HD_SUCCESS, 1 otherwise (error)
     
    2121    LOAD_BDA_SEGMENT_TO ds, ax, !
    2222    xchg    ah, [BDA.bHDLastSt]     ; Load and clear last error
    23     call    HError_SetErrorCodeToIntpackInSSBPfromAH
     23    call    Int13h_SetErrorCodeToIntpackInSSBPfromAH
    2424    jmp     Int13h_ReturnFromHandlerWithoutStoringErrorCode
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH23h_HFeatures.asm

    r148 r150  
    1414;       DL:     Translated Drive number
    1515;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    16 ;       SS:BP:  Ptr to INTPACK
    17 ;   Parameters on INTPACK in SS:BP:
     16;       SS:BP:  Ptr to IDEPACK
     17;   Parameters on INTPACK:
    1818;       AL:     Feature Number (parameter to Features Register = subcommand)
    19 ;   (Parameter registers are undocumented, there are specific for this BIOS):
    20 ;       BH:     Parameter to Sector Count Register (subcommand specific)
    21 ;       BL:     Parameter to Sector Number Register (subcommand specific)
    22 ;       CL:     Parameter to Low Cylinder Register (subcommand specific)
    23 ;       CH:     Parameter to High Cylinder Register (subcommand specific)
    24 ;   Returns with INTPACK in SS:BP:
     19;   (Parameter registers are undocumented, these are specific for this BIOS):
     20;       BL:     Parameter to Sector Count Register (subcommand specific)
     21;       BH:     Parameter to LBA Low / Sector Number Register (subcommand specific)
     22;       CL:     Parameter to LBA Middle / Cylinder Low Register (subcommand specific)
     23;       CH:     Parameter to LBA High / Cylinder High Register (subcommand specific)
     24;   Returns with INTPACK:
    2525;       AH:     Int 13h return status
    2626;       CF:     0 if succesfull, 1 if error
     
    2828ALIGN JUMP_ALIGN
    2929AH23h_HandlerForSetControllerFeatures:
     30    xchg    si, ax      ; SI = Feature Number
     31    mov     dx, [bp+IDEPACK.intpack+INTPACK.bx]
    3032%ifndef USE_186
    3133    call    AH23h_SetControllerFeatures
     
    4042; AH23h_SetControllerFeatures
    4143;   Parameters:
    42 ;       AL:     Feature Number (parameter to Features Register = subcommand)
    43 ;       BH:     Parameter to Sector Count Register (subcommand specific)
    44 ;       BL:     Parameter to Sector Number Register (subcommand specific)
    45 ;       CL:     Parameter to Low Cylinder Register (subcommand specific)
    46 ;       CH:     Parameter to High Cylinder Register (subcommand specific)
     44;       DL:     Parameter to Sector Count Register (subcommand specific)
     45;       DH:     Parameter to LBA Low / Sector Number Register (subcommand specific)
     46;       CL:     Parameter to LBA Middle / Cylinder Low Register (subcommand specific)
     47;       CH:     Parameter to LBA High / Cylinder High Register (subcommand specific)
     48;       SI:     Feature Number (parameter to Features Register = subcommand)
    4749;       DS:DI:  Ptr to DPT (in RAMVARS segment)
     50;       SS:BP:  Ptr to IDEPACK
    4851;   Returns:
    4952;       AH:     Int 13h return status
    5053;       CF:     0 if succesfull, 1 if error
    5154;   Corrupts registers:
    52 ;       AX, BX, CX, DX, SI
     55;       AL, BX, CX, DX
    5356;--------------------------------------------------------------------
    5457ALIGN JUMP_ALIGN
    5558AH23h_SetControllerFeatures:
    56     ; Backup AL and BH to SI
    57     mov     ah, bh
    58     xchg    si, ax
    59 
    60     ; Select Master or Slave and wait until ready
    61     call    HDrvSel_SelectDriveAndDisableIRQ
    62     jc      SHORT .ReturnWithErrorCodeInAH
    63 
    64     ; Output Feature Number
    65     mov     ax, si                      ; Feature number to AL
    66     mov     dx, [RAMVARS.wIdeBase]      ; Load base port address
    67     inc     dx                          ; REGW_IDE_FEAT
    68     out     dx, al
    69 
    70     ; Output parameters to Sector Number Register and Cylinder Registers
    71     xor     bh, bh                      ; Zero head number
    72     dec     dx                          ; Back to base port address
    73     call    HCommand_OutputTranslatedLCHSaddress
    74 
    75     ; Output parameter to Sector Count Register and command
    76     xchg    ax, si                      ; Sector Count Reg param to AH
    77     mov     al, ah                      ; Sector Count Reg param to AL
    78     mov     ah, HCMD_SET_FEAT           ; Load Set Features command to AH
    79     call    HCommand_OutputSectorCountAndCommand
    80 
    81     jmp     HStatus_WaitBsyDefTime      ; Wait until drive ready
    82 .ReturnWithErrorCodeInAH:
    83     ret
     59    mov     al, COMMAND_SET_FEATURES
     60    mov     bx, TIMEOUT_AND_STATUS_TO_WAIT(TIMEOUT_BSY, FLG_STATUS_BSY)
     61    jmp     Idepack_StoreNonExtParametersAndIssueCommandFromAL
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH24h_HSetBlocks.asm

    r148 r150  
    1313;       DL:     Translated Drive number
    1414;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    15 ;       SS:BP:  Ptr to INTPACK
    16 ;   Parameters on INTPACK in SS:BP:
     15;       SS:BP:  Ptr to IDEPACK
     16;   Parameters on INTPACK:
    1717;       AL:     Number of Sectors per Block (1, 2, 4, 8, 16, 32, 64 or 128)
    18 ;   Returns with INTPACK in SS:BP:
     18;   Returns with INTPACK:
    1919;       AH:     Int 13h return status
    2020;       CF:     0 if succesfull, 1 if error
     
    2222ALIGN JUMP_ALIGN
    2323AH24h_HandlerForSetMultipleBlocks:
     24    test    WORD [di+DPT.wFlags], FLG_DPT_BLOCK_MODE_SUPPORTED
     25    jnz     SHORT .TryToSetBlockMode
     26    stc
     27    mov     ah, RET_HD_INVALID
     28    jmp     Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     29
     30ALIGN JUMP_ALIGN
     31.TryToSetBlockMode:
    2432%ifndef USE_186
    2533    call    AH24h_SetBlockSize
     
    3240
    3341;--------------------------------------------------------------------
    34 ; Sets block size for block mode transfers.
    35 ;
    3642; AH24h_SetBlockSize
    3743;   Parameters:
    3844;       AL:     Number of Sectors per Block (1, 2, 4, 8, 16, 32, 64 or 128)
    3945;       DS:DI:  Ptr to DPT (in RAMVARS segment)
     46;       SS:BP:  Ptr to IDEPACK
    4047;   Returns:
    4148;       AH:     Int 13h return status
     
    4653ALIGN JUMP_ALIGN
    4754AH24h_SetBlockSize:
    48     ; Select Master or Slave and wait until ready
    49     mov     bl, al                              ; Backup block size
    50     call    HDrvSel_SelectDriveAndDisableIRQ    ; Select drive and wait until ready
    51     jc      SHORT .ReturnWithErrorCodeInAH      ; Return if error
    52 
    53     ; Output block size and command
    54     mov     al, bl                              ; Restore block size to AL
    55     mov     ah, HCMD_SET_MUL                    ; Load command to AH
    56     mov     dx, [RAMVARS.wIdeBase]              ; Load base port address
    57     add     dx, BYTE REG_IDE_CNT
    58     call    HCommand_OutputSectorCountAndCommand
    59     call    HStatus_WaitBsyDefTime              ; Wait until drive not busy
     55    MIN_U   al, MAX_SUPPORTED_BLOCK_SIZE_IN_SECTORS
     56    push    ax
     57    xchg    dx, ax          ; DL = Block size (Sector Count Register)
     58    mov     al, COMMAND_SET_MULTIPLE_MODE
     59    mov     bx, TIMEOUT_AND_STATUS_TO_WAIT(TIMEOUT_DRDY, FLG_STATUS_DRDY)
     60    call    Idepack_StoreNonExtParametersAndIssueCommandFromAL
     61    pop     bx
    6062    jc      SHORT .DisableBlockMode
    6163
    6264    ; Store new block size to DPT and return
    63     mov     [di+DPT.bSetBlock], bl              ; Store new block size
    64     xor     ah, ah                              ; Zero AH and CF since success
     65    mov     [di+DPT_ATA.bSetBlock], bl              ; Store new block size
    6566    ret
    6667.DisableBlockMode:
    67     mov     BYTE [di+DPT.bSetBlock], 1          ; Disable block mode
    68 .ReturnWithErrorCodeInAH:
     68    mov     BYTE [di+DPT_ATA.bSetBlock], 1          ; Disable block mode
    6969    ret
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH25h_HDrvID.asm

    r148 r150  
    1313;       DL:     Translated Drive number
    1414;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    15 ;       SS:BP:  Ptr to INTPACK
    16 ;   Parameters on INTPACK in SS:BP:
     15;       SS:BP:  Ptr to IDEPACK
     16;   Parameters on INTPACK:
    1717;       ES:BX:  Ptr to buffer to receive 512-byte drive information
    18 ;   Returns with INTPACK in SS:BP:
     18;   Returns with INTPACK:
    1919;       AH:     Int 13h return status
    2020;       CF:     0 if succesfull, 1 if error
     
    2222ALIGN JUMP_ALIGN
    2323AH25h_HandlerForGetDriveInformation:
    24     ; Wait until previously selected drive is ready
    25     call    HDrvSel_SelectDriveAndDisableIRQ
    26     jc      SHORT .ReturnWithErrorCodeInAH      ; Return if error
     24    push    bp
    2725
    28     ; Get drive information
    29     mov     bx, [bp+INTPACK.bx]
    30     call    HPIO_NormalizeDataPointer
    31     push    bx
    32     mov     dx, [RAMVARS.wIdeBase]      ; Load base port address
    33     eMOVZX  bx, BYTE [di+DPT.bIdeOff]   ; Load offset to IDEVARS
    34     mov     bl, [cs:bx+IDEVARS.bBusType]; Load bus type to BL
    35     mov     bh, [di+DPT.bDrvSel]        ; Load drive sel byte to BH
    36     pop     di                          ; Pop buffer offset to DI
    37     call    AH25h_GetDriveInfo          ; Get drive information
    38 .ReturnWithErrorCodeInAH:
     26    mov     si, [bp+IDEPACK.intpack+INTPACK.bx]
     27    call    AccessDPT_GetDriveSelectByteToAL
     28    mov     bh, al
     29    eMOVZX  ax, BYTE [di+DPT.bIdevarsOffset]
     30    xchg    bp, ax
     31    call    Device_IdentifyToBufferInESSIwithDriveSelectByteInBH
     32
     33    pop     bp
    3934    jmp     Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
    40 
    41 
    42 ;--------------------------------------------------------------------
    43 ; Gets drive information using Identify Device command.
    44 ;
    45 ; AH25h_GetDriveInfo
    46 ;   Parameters:
    47 ;       BH:     Drive Select byte for Drive and Head Select Register
    48 ;       BL:     Bus type
    49 ;       DX:     IDE Controller base port address
    50 ;       DS:     Segment to RAMVARS
    51 ;       ES:DI:  Ptr to buffer to receive 512 byte drive information
    52 ;   Returns:
    53 ;       AH:     Int 13h return status (will be stored to BDA)
    54 ;       CF:     0 if succesfull, 1 if error
    55 ;   Corrupts registers:
    56 ;       AL, CX
    57 ;--------------------------------------------------------------------
    58 ALIGN JUMP_ALIGN
    59 AH25h_GetDriveInfo:
    60     push    di
    61     push    dx
    62     push    bx
    63 
    64     ; Select Master or Slave drive.
    65     ; DO NOT WAIT UNTIL CURRENTLY SELECTED IS READY!
    66     ; It makes slave drive detection impossible if master is not present.
    67     mov     [RAMVARS.wIdeBase], dx      ; Store IDE Base port to RAMVARS
    68     add     dx, BYTE REG_IDE_DRVHD      ; DX to Drive and Head Sel Register
    69     mov     al, bh                      ; Drive Select byte to AL
    70     out     dx, al                      ; Select Master or Slave drive
    71     sub     dx, BYTE REG_IDE_DRVHD      ; Back to IDE Base port
    72 
    73     ; Wait until ready to accept commands
    74     xor     bh, bh                      ; BX now contains bus type
    75     mov     cl, B_TIMEOUT_DRVINFO       ; Load short timeout
    76     cmp     [RAMVARS.bDrvCnt], bh       ; Detecting first drive?
    77     eCMOVE  cl, B_TIMEOUT_RESET         ;  If so, load long timeout
    78     call    HStatus_WaitRdy             ; Wait until ready to accept commands
    79     jc      SHORT .ReturnWithErrorCodeInAH
    80 
    81     ; Output command
    82     mov     al, HCMD_ID_DEV             ; Load Identify Device command to AL
    83     out     dx, al                      ; Output command
    84     call    HStatus_WaitDrqDefTime      ; Wait until ready to transfer (no IRQ!)
    85     jc      SHORT .ReturnWithErrorCodeInAH
    86 
    87     ; Transfer data
    88     sub     dx, BYTE REGR_IDE_ST        ; DX to IDE Data Reg
    89     mov     cx, 256                     ; Transfer 256 words (single sector)
    90     cld                                 ; INSW to increment DI
    91     call    [cs:bx+g_rgfnPioRead]       ; Read ID sector
    92     call    HStatus_WaitRdyDefTime      ; Wait until drive ready
    93 
    94 .ReturnWithErrorCodeInAH:
    95     pop     bx
    96     pop     dx
    97     pop     di
    98     ret
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH2h_HRead.asm

    r148 r150  
    1313;       DL:     Translated Drive number
    1414;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    15 ;       SS:BP:  Ptr to INTPACK
    16 ;   Parameters on INTPACK in SS:BP:
    17 ;       AL:     Number of sectors to read (1...255)
     15;       SS:BP:  Ptr to IDEPACK
     16;   Parameters on INTPACK:
     17;       AL:     Number of sectors to read (1...255, 0=256)
    1818;       CH:     Cylinder number, bits 7...0
    1919;       CL:     Bits 7...6: Cylinder number bits 9 and 8
     
    2121;       DH:     Starting head number (0...255)
    2222;       ES:BX:  Pointer to buffer recieving data
    23 ;   Returns with INTPACK in SS:BP:
     23;   Returns with INTPACK:
    2424;       AH:     Int 13h/40h floppy return status
    2525;       AL:     Burst error length if AH returns 11h, undefined otherwise
     
    2828ALIGN JUMP_ALIGN
    2929AH2h_HandlerForReadDiskSectors:
    30     test    al, al                      ; Invalid sector count?
    31     jz      SHORT AH2h_ZeroCntErr       ;  If so, return with error
    32 
    33     ; Select sector or block mode command
    34     mov     ah, HCMD_READ_SECT          ; Load sector mode command
    35     cmp     BYTE [di+DPT.bSetBlock], 1  ; Block mode enabled?
    36     eCMOVA  ah, HCMD_READ_MUL           ; Load block mode command
    37 
    38     ; Transfer data
    39     call    HCommand_OutputCountAndLCHSandCommand
    40     jc      SHORT .ReturnWithErrorCodeInAH
    41     mov     bx, [bp+INTPACK.bx]
    42     call    HPIO_ReadBlock              ; Read data from IDE-controller
    43 .ReturnWithErrorCodeInAH:
     30    mov     ah, COMMAND_READ_SECTORS    ; Load sector mode command
     31    test    WORD [di+DPT.wFlags], FLG_DPT_BLOCK_MODE_SUPPORTED
     32    eCMOVNZ ah, COMMAND_READ_MULTIPLE   ; Load block mode command
     33    mov     bx, TIMEOUT_AND_STATUS_TO_WAIT(TIMEOUT_DRQ, FLG_STATUS_DRQ)
     34    mov     si, [bp+IDEPACK.intpack+INTPACK.bx]
     35%ifdef USE_186
     36    push    Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     37    jmp     Idepack_TranslateOldInt13hAddressAndIssueCommandFromAH
     38%else
     39    call    Idepack_TranslateOldInt13hAddressAndIssueCommandFromAH
    4440    jmp     Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
    45 
    46 ; Invalid sector count (also for AH=3h and AH=4h)
    47 AH2h_ZeroCntErr:
    48     mov     ah, RET_HD_INVALID          ; Invalid value passed
    49     jmp     Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     41%endif
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH3h_HWrite.asm

    r148 r150  
    1313;       DL:     Translated Drive number
    1414;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    15 ;       SS:BP:  Ptr to INTPACK
    16 ;   Parameters on INTPACK in SS:BP:
     15;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
     16;   Parameters on INTPACK:
    1717;       AL:     Number of sectors to write
    1818;       CH:     Cylinder number, bits 7...0
     
    2121;       DH:     Starting head number (0...255)
    2222;       ES:BX:  Pointer to source data
    23 ;   Returns with INTPACK in SS:BP:
     23;   Returns with INTPACK:
    2424;       AH:     Int 13h/40h floppy return status
    2525;       CF:     0 if successfull, 1 if error
     
    2727ALIGN JUMP_ALIGN
    2828AH3h_HandlerForWriteDiskSectors:
    29     test    al, al                      ; Invalid sector count?
    30     jz      SHORT AH2h_ZeroCntErr       ;  If so, return with error
    31 
    32     ; Select sector or block mode command
    33     mov     ah, HCMD_WRITE_SECT         ; Load sector mode command
    34     cmp     BYTE [di+DPT.bSetBlock], 1  ; Block mode enabled?
    35     eCMOVA  ah, HCMD_WRITE_MUL          ; Load block mode command
    36 
    37     ; Transfer data
    38     call    HCommand_OutputCountAndLCHSandCommand
    39     jc      SHORT .ReturnWithErrorCodeInAH
    40     mov     bx, [bp+INTPACK.bx]
    41     call    HPIO_WriteBlock             ; Write data to IDE-controller
    42 .ReturnWithErrorCodeInAH:
     29    ; Prepare parameters
     30    mov     ah, COMMAND_WRITE_SECTORS   ; Load sector mode command
     31    test    WORD [di+DPT.wFlags], FLG_DPT_BLOCK_MODE_SUPPORTED
     32    eCMOVNZ ah, COMMAND_WRITE_MULTIPLE  ; Load block mode command
     33    mov     bx, TIMEOUT_AND_STATUS_TO_WAIT(TIMEOUT_DRQ, FLG_STATUS_DRQ)
     34    mov     si, [bp+IDEPACK.intpack+INTPACK.bx]
     35%ifdef USE_186
     36    push    Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     37    jmp     Idepack_TranslateOldInt13hAddressAndIssueCommandFromAH
     38%else
     39    call    Idepack_TranslateOldInt13hAddressAndIssueCommandFromAH
    4340    jmp     Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     41%endif
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH4h_HVerify.asm

    r148 r150  
    2626ALIGN JUMP_ALIGN
    2727AH4h_HandlerForVerifyDiskSectors:
    28     test    al, al                      ; Invalid sector count?
    29     jz      SHORT AH2h_ZeroCntErr       ;  If so, return with error
    30 
    31     mov     ah, HCMD_VERIFY_SECT        ; Load command to AH
    32     call    HCommand_OutputCountAndLCHSandCommand
    33     jc      SHORT .ReturnWithErrorCodeInAH
    34     mov     bx, di                      ; DS:BX now points to DPT
    35     call    HStatus_WaitIrqOrRdy        ; Wait for IRQ or RDY
    36 .ReturnWithErrorCodeInAH:
     28    mov     ah, COMMAND_WRITE_SECTORS
     29    mov     bx, TIMEOUT_AND_STATUS_TO_WAIT(TIMEOUT_DRQ, FLG_STATUS_DRDY)
     30%ifdef USE_186
     31    push    Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     32    jmp     Idepack_TranslateOldInt13hAddressAndIssueCommandFromAH
     33%else
     34    call    Idepack_TranslateOldInt13hAddressAndIssueCommandFromAH
    3735    jmp     Int13h_ReturnFromHandlerAfterStoringErrorCodeFromAH
     36%endif
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH8h_HParams.asm

    r148 r150  
    1212;       DL:     Translated Drive number
    1313;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    14 ;       SS:BP:  Ptr to INTPACK
    15 ;   Returns with INTPACK in SS:BP:
     14;       SS:BP:  Ptr to IDEPACK
     15;   Returns with INTPACK:
    1616;       CH:     Maximum cylinder number, bits 7...0
    1717;       CL:     Bits 7...6: Cylinder number bits 9...8
     
    3434    call    RamVars_GetCountOfKnownDrivesToDL
    3535.ReturnAfterStoringValuesToIntpack:
    36     mov     [bp+INTPACK.cx], cx
    37     mov     [bp+INTPACK.dx], dx
     36    mov     [bp+IDEPACK.intpack+INTPACK.cx], cx
     37    mov     [bp+IDEPACK.intpack+INTPACK.dx], dx
    3838    xor     ah, ah
    3939.ReturnErrorFromPreviousInt13hHandler:
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AH9h_HInit.asm

    r148 r150  
    1212;       DL:     Translated Drive number
    1313;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    14 ;       SS:BP:  Ptr to INTPACK
    15 ;   Returns with INTPACK in SS:BP:
     14;       SS:BP:  Ptr to IDEPACK
     15;   Returns with INTPACK:
    1616;       AH:     Int 13h return status
    1717;       CF:     0 if succesfull, 1 if error
     
    3434;   Parameters:
    3535;       DS:DI:  Ptr to DPT (in RAMVARS segment)
     36;       SS:BP:  Ptr to IDEPACK
    3637;   Returns:
    3738;       AH:     Int 13h return status
     
    4546
    4647    ; Try to select drive and wait until ready
    47     or      BYTE [di+DPT.bReset], MASK_RESET_ALL        ; Everything uninitialized
    48     call    HDrvSel_SelectDriveAndDisableIRQ
     48    or      WORD [di+DPT.wFlags], MASK_DPT_RESET        ; Everything uninitialized
     49    call    AccessDPT_GetDriveSelectByteToAL
     50    mov     [bp+IDEPACK.bDrvAndHead], al
     51    call    Device_SelectDrive
    4952    jc      SHORT .ReturnNotSuccessfull
    50     and     BYTE [di+DPT.bReset], ~FLG_RESET_nDRDY      ; Clear since success
     53    and     WORD [di+DPT.wFlags], ~FLG_DPT_RESET_nDRDY  ; Clear since success
    5154
    5255    ; Initialize CHS parameters if LBA is not used
    53     call    AH9h_InitializeDeviceParameters
     56    call    InitializeDeviceParameters
    5457    jc      SHORT .RecalibrateDrive
    55     and     BYTE [di+DPT.bReset], ~FLG_RESET_nINITPRMS
     58    and     WORD [di+DPT.wFlags], ~FLG_DPT_RESET_nINITPRMS
    5659
    5760    ; Recalibrate drive by seeking to cylinder 0
    58 ALIGN JUMP_ALIGN
    5961.RecalibrateDrive:
    6062    call    AH11h_RecalibrateDrive
    6163    jc      SHORT .InitializeBlockMode
    62     and     BYTE [di+DPT.bReset], ~FLG_RESET_nRECALIBRATE
     64    and     WORD [di+DPT.wFlags], ~FLG_DPT_RESET_nRECALIBRATE
    6365
    6466    ; Initialize block mode transfers
    6567.InitializeBlockMode:
    66     call    AH9h_InitializeBlockMode
     68    call    InitializeBlockMode
    6769    jc      SHORT .ReturnNotSuccessfull
    68     and     BYTE [di+DPT.bReset], ~FLG_RESET_nSETBLOCK  ; Keeps CF clear
     70    and     WORD [di+DPT.wFlags], ~FLG_DPT_RESET_nSETBLOCK  ; Keeps CF clear
    6971
    7072.ReturnNotSuccessfull:
     
    7476
    7577;--------------------------------------------------------------------
    76 ; Sends Initialize Device Parameters command to IDE Hard Disk.
    77 ; Initialization is used to initialize logical CHS parameters. Drives
    78 ; may not support all CHS values.
    79 ; This command is only supported by drives that supports CHS addressing.
    80 ;
    81 ; AH9h_InitializeDeviceParameters
     78; InitializeDeviceParameters
    8279;   Parameters:
    83 ;       DS:DI:  Ptr to DPT
    84 ;   Returns:
    85 ;       AH:     BIOS Error code
    86 ;       CF:     Cleared if succesfull
    87 ;               Set if any error
    88 ;   Corrupts registers:
    89 ;       AL, BX, CX
    90 ;--------------------------------------------------------------------
    91 ALIGN JUMP_ALIGN
    92 AH9h_InitializeDeviceParameters:
    93     ; No need to initialize CHS parameters if LBA mode enabled
    94     test    BYTE [di+DPT.bDrvSel], FLG_IDE_DRVHD_LBA    ; Clears CF
    95     jnz     SHORT .Return
    96 
    97     push    dx
    98     mov     bh, [di+DPT.bPHeads]
    99     dec     bh                      ; Max head number
    100     mov     dx, [RAMVARS.wIdeBase]
    101     call    HCommand_OutputTranslatedLCHSaddress
    102     mov     ah, HCMD_INIT_DEV
    103     mov     al, [di+DPT.bPSect]     ; Sectors per track
    104     call    HCommand_OutputSectorCountAndCommand
    105     call    HStatus_WaitBsyDefTime  ; Wait until drive ready (DRDY won't be set!)
    106     pop     dx
    107 .Return:
    108     ret
    109 
    110 
    111 ;--------------------------------------------------------------------
    112 ; Initializes block mode transfers.
    113 ;
    114 ; AH9h_InitializeBlockMode
    115 ;   Parameters:
    116 ;       DS:DI:  Ptr to DPT
     80;       DS:DI:  Ptr to DPT (in RAMVARS segment)
     81;       SS:BP:  Ptr to IDEPACK
    11782;   Returns:
    11883;       AH:     BIOS Error code
     
    12388;--------------------------------------------------------------------
    12489ALIGN JUMP_ALIGN
    125 AH9h_InitializeBlockMode:
    126     mov     ax, FLG_DRVPARAMS_BLOCKMODE
    127     call    AccessDPT_TestIdeVarsFlagsForMasterOrSlaveDrive
    128     jz      SHORT .Return               ; Block mode disabled (CF cleared)
    129     eMOVZX  ax, BYTE [di+DPT.bMaxBlock] ; Load max block size, zero AH
    130     test    al, al                      ; Block mode supported? (clears CF)
    131     jz      SHORT .Return               ;  If not, return
     90InitializeDeviceParameters:
     91    ; No need to initialize CHS parameters if LBA mode enabled
     92    test    BYTE [di+DPT.wFlags], FLG_DRVNHEAD_LBA  ; Clear CF
     93    jnz     SHORT ReturnSuccessSinceInitializationNotNeeded
     94
     95    ; Initialize Locigal Sectors per Track and Max Head number
     96    mov     ah, [di+DPT.bPchsHeads]
     97    dec     ah                          ; Max Head number
     98    mov     dl, [di+DPT.bPchsSectors]   ; Sectors per Track
     99    mov     al, COMMAND_INITIALIZE_DEVICE_PARAMETERS
     100    mov     bx, TIMEOUT_AND_STATUS_TO_WAIT(TIMEOUT_BSY, FLG_STATUS_BSY)
     101    jmp     Idepack_StoreNonExtParametersAndIssueCommandFromAL
     102
     103
     104;--------------------------------------------------------------------
     105; InitializeBlockMode
     106;   Parameters:
     107;       DS:DI:  Ptr to DPT (in RAMVARS segment)
     108;   Returns:
     109;       AH:     BIOS Error code
     110;       CF:     Cleared if succesfull
     111;               Set if any error
     112;   Corrupts registers:
     113;       AL, BX, CX, DX
     114;--------------------------------------------------------------------
     115ALIGN JUMP_ALIGN
     116InitializeBlockMode:
     117    test    WORD [di+DPT.wFlags], FLG_DPT_BLOCK_MODE_SUPPORTED  ; Clear CF
     118    jz      SHORT ReturnSuccessSinceInitializationNotNeeded
     119
     120    mov     al, [di+DPT_ATA.bMaxBlock]  ; Load max block size, zero AH
    132121    jmp     AH24h_SetBlockSize
    133 .Return:
     122ReturnSuccessSinceInitializationNotNeeded:
    134123    ret
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AHCh_HSeek.asm

    r148 r150  
    1313;       DL:     Translated Drive number
    1414;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    15 ;       SS:BP:  Ptr to INTPACK
    16 ;   Parameters on INTPACK in SS:BP:
     15;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
     16;   Parameters on INTPACK:
    1717;       CH:     Cylinder number, bits 7...0
    1818;       CL:     Bits 7...6: Cylinder number bits 9 and 8
    1919;               Bits 5...0: Starting sector number (1...63)
    2020;       DH:     Starting head number (0...255)
    21 ;   Returns with INTPACK in SS:BP:
     21;   Returns with INTPACK:
    2222;       AH:     BIOS Error code
    2323;       CF:     0 if succesfull, 1 if error
     
    3333%endif
    3434
    35 
    3635;--------------------------------------------------------------------
    3736; AHCh_SeekToCylinder
     
    4241;       DH:     Starting head number (0...255)
    4342;       DS:DI:  Ptr to DPT (in RAMVARS segment)
     43;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
    4444;   Returns:
    4545;       AH:     BIOS Error code
     
    4949;--------------------------------------------------------------------
    5050AHCh_SeekToCylinder:
    51     mov     ax, HCMD_SEEK<<8            ; Load cmd to AH, AL=zero sector cnt
    52     call    HCommand_OutputCountAndLCHSandCommand
    53     jc      SHORT .ReturnWithErrorCodeInAH
    54     mov     bx, di                      ; DS:BX now points to DPT
    55     jmp     HStatus_WaitIrqOrRdy        ; Wait for IRQ or RDY
    56 .ReturnWithErrorCodeInAH:
    57     ret
     51    mov     ah, COMMAND_SEEK
     52    mov     bx, TIMEOUT_AND_STATUS_TO_WAIT(TIMEOUT_DRQ, FLG_STATUS_DRDY)
     53    jmp     Idepack_TranslateOldInt13hAddressAndIssueCommandFromAH
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/AHDh_HReset.asm

    r148 r150  
    1212;       DL:     Translated Drive number
    1313;       DS:DI:  Ptr to DPT (in RAMVARS segment)
    14 ;       SS:BP:  Ptr to INTPACK
    15 ;   Returns with INTPACK in SS:BP:
     14;       SS:BP:  Ptr to IDEPACK
     15;   Returns with INTPACK:
    1616;       AH:     Int 13h return status
    1717;       CF:     0 if succesfull, 1 if error
     
    3535;       DL:     Drive number
    3636;       DS:     RAMVARS segment
     37;       SS:BP:  Ptr to IDEPACK
    3738;   Returns:
    3839;       AH:     Int 13h return status
    3940;       CF:     0 if succesfull, 1 if error
    4041;   Corrupts registers:
    41 ;       AL, CX, DI
     42;       AL, CX, SI, DI
    4243;--------------------------------------------------------------------
    4344ALIGN JUMP_ALIGN
     
    4849    call    FindDPT_ForDriveNumber      ; DS:DI now points to DPT
    4950    call    Interrupts_UnmaskInterruptControllerForDriveInDSDI
    50     call    AHDh_ResetMasterAndSlave
     51    call    Device_ResetMasterAndSlaveController
    5152    ;jc     SHORT .ReturnError          ; CF would be set if slave drive present without master
    5253                                        ; (error register has special values after reset)
    5354
    5455    ; Initialize Master and Slave drives
    55     mov     dx, [RAMVARS.wIdeBase]      ; Load base port address
    56     call    AHDh_InitializeMasterAndSlave
     56    eMOVZX  bx, BYTE [di+DPT.bIdevarsOffset]
     57    mov     dx, [cs:bx+IDEVARS.wPort]
     58    call    InitializeMasterAndSlaveDriveFromPortInDX
    5759
    5860    pop     bx
     
    6264
    6365;--------------------------------------------------------------------
    64 ; Resets Master and Slave drives at wanted port.
    65 ; Both IDE drives will be reset. It is not possible to reset
    66 ; Master or Slave only.
    67 ;
    68 ; AHDh_ResetMasterAndSlave
    69 ;   Parameters:
    70 ;       DS:DI:  Ptr to DPT for Master or Slave drive
    71 ;   Returns:
    72 ;       CF:     0 if reset succesfull
    73 ;               1 if any error
    74 ;   Corrupts registers:
    75 ;       AX, BX, CX, DX
    76 ;--------------------------------------------------------------------
    77 ALIGN JUMP_ALIGN
    78 AHDh_ResetMasterAndSlave:
    79     ; Reset controller
    80     ; HSR0: Set_SRST
    81     mov     al, [di+DPT.bDrvCtrl]       ; Load value for ACR
    82     or      al, FLG_IDE_CTRL_SRST       ; Set Reset bit
    83     call    HDrvSel_OutputDeviceControlByte
    84     mov     ax, 5                       ; Delay at least 5us
    85     call    HTimer_DelayMicrosecondsFromAX
    86 
    87     ; HSR1: Clear_wait
    88     mov     al, [di+DPT.bDrvCtrl]       ; Load value for ACR
    89     out     dx, al                      ; End Reset
    90     mov     ax, 2000                    ; Delay at least 2ms
    91     call    HTimer_DelayMicrosecondsFromAX
    92 
    93     ; HSR2: Check_status
    94     mov     cl, B_TIMEOUT_RESET         ; Reset timeout delay
    95     jmp     HStatus_WaitBsy
    96 
    97 
    98 ;--------------------------------------------------------------------
    99 ; Initializes Master and Slave drive.
    100 ;
    101 ; AHDh_InitializeMasterAndSlave
     66; InitializeMasterAndSlaveDriveFromPortInDX
    10267;   Parameters:
    10368;       DX:     IDE Base Port address
     69;       SS:BP:  Ptr to IDEPACK
    10470;   Returns:
    10571;       AH:     Error code
     
    10773;               1 if any error
    10874;   Corrupts registers:
    109 ;       AL, BX, CX, DX, DI
     75;       AL, BX, CX, DX, SI, DI
    11076;--------------------------------------------------------------------
    11177ALIGN JUMP_ALIGN
    112 AHDh_InitializeMasterAndSlave:
     78InitializeMasterAndSlaveDriveFromPortInDX:
    11379    push    dx                          ; Store base port address
    11480    xor     cx, cx                      ; Assume no errors
    115     call    FindDPT_ForIdeMasterAtPort
     81    call    FindDPT_ToDSDIForIdeMasterAtPortDX
    11682    jnc     SHORT .InitializeSlave      ; Master drive not present
    11783    call    AH9h_InitializeDriveForUse
     
    11985.InitializeSlave:
    12086    pop     dx                          ; Restore base port address
    121     call    FindDPT_ForIdeSlaveAtPort
     87    call    FindDPT_ToDSDIForIdeSlaveAtPortDX
    12288    jnc     SHORT .CombineErrors        ; Slave drive not present
    12389    call    AH9h_InitializeDriveForUse
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/Common/HAddress.asm

    r3 r150  
    1 ; File name     :   HAddress.asm
    2 ; Project name  :   IDE BIOS
    3 ; Created date  :   11.3.2010
    4 ; Last update   :   4.4.2010
    5 ; Author        :   Tomi Tilli
     1; Project name  :   XTIDE Universal BIOS
    62; Description   :   Functions for address translations.
    73
     
    95SECTION .text
    106
     7; Jump table for conversion functions
     8ALIGN WORD_ALIGN
     9g_rgfnAddressTranslation:
     10    dw      DoNotConvertLCHS                    ; 0, ADDR_DPT_LCHS
     11    dw      ConvertLCHStoPCHS                   ; 1, ADDR_DPT_PCHS
     12    dw      ConvertLCHStoLBARegisterValues      ; 2, ADDR_DPT_LBA28
     13    dw      ConvertLCHStoLBARegisterValues      ; 3, ADDR_DPT_LBA48
     14
     15
    1116;--------------------------------------------------------------------
    12 ; Outputs sector count, L-CHS address and command to IDE registers.
    13 ; This function does not wait until command has been completed.
    14 ;
    15 ; HAddress_ConvertParamsFromBiosLCHStoIDE
     17; HAddress_OldInt13hAddressToIdeAddress
    1618;   Parameters:
    1719;       CH:     Cylinder number, bits 7...0
     
    2830;       AX, DX
    2931;--------------------------------------------------------------------
    30 ALIGN WORD_ALIGN
    31 g_rgfnAddressTranslation:
    32     dw      HAddress_DoNotConvertLCHS                   ; 0, ADDR_DPT_LCHS
    33     dw      HAddress_ConvertLCHStoPCHS                  ; 1, ADDR_DPT_PCHS
    34     dw      HAddress_ConvertLCHStoLBARegisterValues     ; 2, ADDR_DPT_LBA28
    35     dw      HAddress_ConvertLCHStoLBARegisterValues     ; 3, ADDR_DPT_LBA48
    36 
    3732ALIGN JUMP_ALIGN
    38 HAddress_ConvertParamsFromBiosLCHStoIDE:
    39     mov     bl, [di+DPT.bFlags]
    40     and     bx, BYTE MASK_DPT_ADDR                      ; Addressing mode to BX
     33HAddress_OldInt13hAddressToIdeAddress:
     34    call    AccessDPT_GetAddressingModeForWordLookToBX
    4135    push    WORD [cs:bx+g_rgfnAddressTranslation]       ; Push return address
    42     ; Fall to HAddress_ExtractLCHSFromBiosParams
     36    ; Fall to HAddress_ExtractLCHSparametersFromOldInt13hAddress
    4337
    4438;---------------------------------------------------------------------
    45 ; Extracts L-CHS parameters from BIOS function parameters.
    46 ;
    47 ; HAddress_ExtractLCHSFromBiosParams:
     39; HAddress_ExtractLCHSparametersFromOldInt13hAddress
    4840;   Parameters:
    4941;       CH:     Cylinder number, bits 7...0
     
    5850;       Nothing
    5951;--------------------------------------------------------------------
    60 ALIGN JUMP_ALIGN
    61 HAddress_ExtractLCHSFromBiosParams:
     52HAddress_ExtractLCHSparametersFromOldInt13hAddress:
    6253    mov     bl, cl              ; Copy sector number...
    6354    and     bl, 3Fh             ; ...and limit to 1...63
     
    7061
    7162;---------------------------------------------------------------------
    72 ; Converts BIOS LCHS parameters to IDE P-CHS parameters.
     63; Converts LCHS parameters to IDE P-CHS parameters.
    7364; PCylinder = (LCylinder << n) + (LHead / PHeadCount)
    7465; PHead     = LHead % PHeadCount
     
    8980;--------------------------------------------------------------------
    9081ALIGN JUMP_ALIGN
    91 HAddress_ConvertLCHStoPCHS:
     82ConvertLCHStoPCHS:
    9283    ; LHead / PHeadCount and LHead % PHeadCount
    9384    eMOVZX  ax, bh                  ; Copy L-CHS Head number to AX
    94     div     BYTE [di+DPT.bPHeads]   ; AL = LHead / PHeadCount, AH = LHead % PHeadCount
     85    div     BYTE [di+DPT.bPchsHeads]; AL = LHead / PHeadCount, AH = LHead % PHeadCount
    9586    mov     bh, ah                  ; Copy P-CHS Head number to BH
    9687    xor     ah, ah                  ; AX = LHead / PHeadCount
     
    9889    ; (LCylinder << n) + (LHead / PHeadCount)
    9990    mov     dx, cx                  ; Copy L-CHS Cylinder number to DX
    100     mov     cl, [di+DPT.bShLtoP]    ; Load shift count
     91    mov     cl, [di+DPT.wFlags]     ; Load shift count
     92    and     cl, MASK_DPT_CHS_SHIFT_COUNT
    10193    shl     dx, cl                  ; DX = LCylinder << n
    10294    add     ax, dx                  ; AX = P-CHS Cylinder number
    10395    mov     cx, ax                  ; Copy P-CHS Cylinder number to CX
    104 ALIGN JUMP_ALIGN
    105 HAddress_DoNotConvertLCHS:
     96DoNotConvertLCHS:
    10697    ret
    10798
     
    109100;---------------------------------------------------------------------
    110101; Converts LCHS parameters to 28-bit LBA address.
     102; Only 24-bits are used since LHCS to LBA28 conversion has 8.4GB limit.
     103; LBA = ((cylToSeek*headsPerCyl+headToSeek)*sectPerTrack)+sectToSeek-1
     104;
    111105; Returned address is in same registers that
    112106; HAddress_DoNotConvertLCHS and HAddress_ConvertLCHStoPCHS returns.
    113107;
    114 ; HAddress_ConvertLCHStoLBARegisterValues:
     108; ConvertLCHStoLBARegisterValues:
    115109;   Parameters:
    116110;       BL:     Sector number (1...63)
     
    127121;--------------------------------------------------------------------
    128122ALIGN JUMP_ALIGN
    129 HAddress_ConvertLCHStoLBARegisterValues:
    130     call    HAddress_ConvertLCHStoLBA28
    131     mov     bl, al                  ; Sector Number Register (LBA 7...0)
    132     mov     cl, ah                  ; Low Cylinder Register (LBA 15...8)
    133     mov     ch, dl                  ; High Cylinder Register (LBA 23...16)
    134     mov     bh, dh                  ; Drive and Head Register (LBA 27...24)
    135     ret
    136 
    137 ;---------------------------------------------------------------------
    138 ; Converts LCHS parameters to 28-bit LBA address.
    139 ; Only 24-bits are used since LHCS to LBA28 conversion has 8.4GB limit.
    140 ; LBA = ((cylToSeek*headsPerCyl+headToSeek)*sectPerTrack)+sectToSeek-1
    141 ;
    142 ; HAddress_ConvertLCHStoLBA28:
    143 ;   Parameters:
    144 ;       BL:     Sector number (1...63)
    145 ;       BH:     Head number (0...255)
    146 ;       CX:     Cylinder number (0...1023)
    147 ;       DS:DI:  Ptr to Disk Parameter Table
    148 ;   Returns:
    149 ;       DX:AX:  28-bit LBA address (DH is always zero)
    150 ;   Corrupts registers:
    151 ;       BX, CX
    152 ;--------------------------------------------------------------------
    153 ALIGN JUMP_ALIGN
    154 HAddress_ConvertLCHStoLBA28:
     123ConvertLCHStoLBARegisterValues:
    155124    ; cylToSeek*headsPerCyl (18-bit result)
    156125    mov     ax, cx                  ; Copy Cylinder number to AX
    157     mul     WORD [di+DPT.wLHeads]   ; DX:AX = cylToSeek*headsPerCyl
     126    eMOVZX  dx, BYTE [di+DPT.bLchsHeads]
     127    mul     dx                      ; DX:AX = cylToSeek*headsPerCyl
    158128
    159129    ; +=headToSeek (18-bit result)
     
    163133
    164134    ; *=sectPerTrack (18-bit by 6-bit multiplication with 24-bit result)
    165     eMOVZX  cx, BYTE [di+DPT.bPSect]; Load Sectors per Track
     135    eMOVZX  cx, BYTE [di+DPT.bPchsSectors]  ; Load Sectors per Track
    166136    xchg    ax, dx                  ; Hiword to AX, loword to DX
    167137    mul     cl                      ; AX = hiword * Sectors per Track
     
    176146    add     ax, bx                  ; Add to loword
    177147    adc     dl, bh                  ; Add possible carry to byte2, BH=zero
     148
     149    ; Copy DX:AX to proper return registers
     150    xchg    bx, ax                  ; BL = Sector Number Register (LBA 7...0)
     151    mov     cl, bh                  ; Low Cylinder Register (LBA 15...8)
     152    mov     ch, dl                  ; High Cylinder Register (LBA 23...16)
     153    mov     bh, dh                  ; Drive and Head Register (LBA 27...24)
    178154    ret
  • trunk/XTIDE_Universal_BIOS/Src/Handlers/Int13h/Common/HTimer.asm

    r148 r150  
    66
    77;--------------------------------------------------------------------
    8 ; HTimer_InitializeTimeoutWithTicksInCL
     8; HTimer_InitializeTimeoutWithTicksInCX
    99;   Parameters:
    10 ;       CL:     Timeout value in system timer ticks
     10;       CX:     Timeout value in system timer ticks
    1111;       DS:     Segment to RAMVARS
    1212;   Returns:
     
    1616;--------------------------------------------------------------------
    1717ALIGN JUMP_ALIGN
    18 HTimer_InitializeTimeoutWithTicksInCL:
    19     xor     ch, ch                          ; Timeout ticks now in CX
     18HTimer_InitializeTimeoutWithTicksInCX:
    2019    mov     [RAMVARS.wTimeoutCounter], cx   ; Store timeout ticks
    2120    call    ReadTimeFromBdaToCX
     
    5554HTimer_DelayMicrosecondsFromAX:
    5655%ifndef USE_AT
    57     mov     ax, 1
     56    mov     ax, 2
    5857    ; Fall to Delay_TimerTicksFromAX
    5958%else
  • trunk/XTIDE_Universal_BIOS/Src/Initialization/DetectDrives.asm

    r120 r150  
    1 ; Project name  :   IDE BIOS
     1; Project name  :   XTIDE Universal BIOS
    22; Description   :   Functions for detecting drive for the BIOS.
    33
     
    4343    push    cx
    4444    mov     ax, g_szMaster
    45     mov     bh, MASK_IDE_DRVHD_SET                              ; Select Master drive
     45    mov     bh, MASK_DRVNHEAD_SET                               ; Select Master drive
    4646    call    StartDetectionWithDriveSelectByteInBHandStringInAX  ; Detect and create DPT + BOOTNFO
    4747
    4848    mov     ax, g_szSlave
    49     mov     bh, MASK_IDE_DRVHD_SET | FLG_IDE_DRVHD_DRV
     49    mov     bh, MASK_DRVNHEAD_SET | FLG_DRVNHEAD_DRV
    5050    call    StartDetectionWithDriveSelectByteInBHandStringInAX
    5151    pop     cx
     
    7878;       ES:     Zero (BDA segment)
    7979;   Returns:
    80 ;       ES:SI   Ptr to ATA information (read with IDENTIFY DEVICE command)
    8180;       CF:     Cleared if ATA-information read successfully
    8281;               Set if any error
    8382;   Corrupts registers:
    84 ;       AX, BL, CX, DX, DI
     83;       AX, BL, CX, DX, SI, DI
    8584;--------------------------------------------------------------------
    8685.ReadAtaInfoFromHardDisk:
    87     mov     bl, [cs:bp+IDEVARS.bBusType]; Load BUS type
    88     mov     dx, [cs:bp+IDEVARS.wPort]   ; Load IDE Base Port address
    89     mov     di, BOOTVARS.rgbAtaInfo     ; ES:DI now points to ATA info location
    90     call    AH25h_GetDriveInfo
     86    mov     si, BOOTVARS.rgbAtaInfo     ; ES:SI now points to ATA info location
     87    push    es
     88    push    si
     89    push    bx
     90    call    Device_IdentifyToBufferInESSIwithDriveSelectByteInBH
     91    pop     bx
     92    pop     si
     93    pop     es
    9194    jnc     SHORT CreateBiosTablesForHardDisk
    9295    ; Fall to .ReadAtapiInfoFromDrive
     
    103106;       BH:     Drive Select byte for Drive and Head Register
    104107;       CS:BP:  Ptr to IDEVARS for the drive
    105 ;       ES:DI   Ptr to ATA information for the drive
     108;       ES:SI   Ptr to ATA information for the drive
    106109;       DS:     RAMVARS segment
    107110;       ES:     BDA/Bootnfo segment
     
    112115;--------------------------------------------------------------------
    113116CreateBiosTablesForHardDisk:
    114     mov     si, di                  ; ES:SI now points to ATA information
    115117    call    CreateDPT_FromAtaInformation
    116118    jc      SHORT .InvalidAtaInfo
  • trunk/XTIDE_Universal_BIOS/Src/Initialization/Initialize.asm

    r130 r150  
    108108;       Nothing
    109109;   Corrupts registers:
    110 ;       AX, BX, CX, DX, DI
     110;       All
    111111;--------------------------------------------------------------------
    112112.ResetDetectedDrives:
    113     jmp     AH0h_ResetHardDisksHandledByOurBIOS
     113    call    Idepack_FakeToSSBP
     114    call    AH0h_ResetHardDisksHandledByOurBIOS
     115    add     sp, BYTE SIZE_OF_FAKE_IDEPACK
     116    ret
  • trunk/XTIDE_Universal_BIOS/Src/Initialization/Interrupts.asm

    r148 r150  
    111111.InstallHighIrqHandler:
    112112    add     bx, BYTE INTV_IRQ8 - 8          ; Interrupt vector number
    113     mov     si, HIRQ_InterruptServiceRoutineForIrqs8to15
     113    mov     si, IdeIrq_InterruptServiceRoutineForIrqs8to15
    114114    jmp     SHORT Interrupts_InstallHandlerToVectorInBXFromCSSI
    115115
     
    126126.InstallLowIrqHandler:
    127127    add     bx, BYTE INTV_IRQ0              ; Interrupt vector number
    128     mov     si, HIRQ_InterruptServiceRoutineForIrqs2to7
     128    mov     si, IdeIrq_InterruptServiceRoutineForIrqs2to7
    129129    ; Fall to Interrupts_InstallHandlerToVectorInBXFromCSSI
    130130
     
    158158;--------------------------------------------------------------------
    159159Interrupts_UnmaskInterruptControllerForDriveInDSDI:
    160     eMOVZX  bx, BYTE [di+DPT.bIdeOff]
     160    eMOVZX  bx, BYTE [di+DPT.bIdevarsOffset]
    161161    mov     al, [cs:bx+IDEVARS.bIRQ]
    162162    test    al, al
  • trunk/XTIDE_Universal_BIOS/Src/Main.asm

    r143 r150  
    2525%include "BootMenu.inc"         ; For Boot Menu
    2626%include "IDE_8bit.inc"         ; For IDE 8-bit data port macros
     27%include "DeviceIDE.inc"        ; For IDE device equates
    2728
    2829
     
    5556    at  ROMVARS.wDisplayMode,   dw  DEFAULT_TEXT_MODE
    5657    at  ROMVARS.wBootTimeout,   dw  30 * TICKS_PER_SECOND   ; Boot Menu selection timeout
    57     at  ROMVARS.bIdeCnt,        db  3                       ; Number of supported controllers
     58    at  ROMVARS.bIdeCnt,        db  4                       ; Number of supported controllers
    5859    at  ROMVARS.bBootDrv,       db  80h                     ; Boot Menu default drive
    5960    at  ROMVARS.bMinFddCnt,     db  0                       ; Do not force minimum number of floppy drives
     
    6263    at  ROMVARS.ideVars0+IDEVARS.wPort,         dw  1F0h            ; Controller Command Block base port
    6364    at  ROMVARS.ideVars0+IDEVARS.wPortCtrl,     dw  3F0h            ; Controller Control Block base port
    64     at  ROMVARS.ideVars0+IDEVARS.bBusType,      db  BUS_TYPE_16     ; Bus type
    65     at  ROMVARS.ideVars0+IDEVARS.bIRQ,          db  14              ; IRQ
     65    at  ROMVARS.ideVars0+IDEVARS.bDevice,       db  DEVICE_16BIT_ATA
     66    at  ROMVARS.ideVars0+IDEVARS.bIRQ,          db  14
    6667    at  ROMVARS.ideVars0+IDEVARS.drvParamsMaster+DRVPARAMS.wFlags,  db  FLG_DRVPARAMS_BLOCKMODE
    6768    at  ROMVARS.ideVars0+IDEVARS.drvParamsSlave+DRVPARAMS.wFlags,   db  FLG_DRVPARAMS_BLOCKMODE
     
    6970    at  ROMVARS.ideVars1+IDEVARS.wPort,         dw  170h            ; Controller Command Block base port
    7071    at  ROMVARS.ideVars1+IDEVARS.wPortCtrl,     dw  370h            ; Controller Control Block base port
    71     at  ROMVARS.ideVars1+IDEVARS.bBusType,      db  BUS_TYPE_16     ; Bus type
    72     at  ROMVARS.ideVars1+IDEVARS.bIRQ,          db  15              ; IRQ
     72    at  ROMVARS.ideVars1+IDEVARS.bDevice,       db  DEVICE_16BIT_ATA
     73    at  ROMVARS.ideVars1+IDEVARS.bIRQ,          db  15
    7374    at  ROMVARS.ideVars1+IDEVARS.drvParamsMaster+DRVPARAMS.wFlags,  db  FLG_DRVPARAMS_BLOCKMODE
    7475    at  ROMVARS.ideVars1+IDEVARS.drvParamsSlave+DRVPARAMS.wFlags,   db  FLG_DRVPARAMS_BLOCKMODE
     
    7677    at  ROMVARS.ideVars2+IDEVARS.wPort,         dw  300h            ; Controller Command Block base port
    7778    at  ROMVARS.ideVars2+IDEVARS.wPortCtrl,     dw  308h            ; Controller Control Block base port
    78     at  ROMVARS.ideVars2+IDEVARS.bBusType,      db  BUS_TYPE_8_DUAL ; Bus type
    79     at  ROMVARS.ideVars2+IDEVARS.bIRQ,          db  0               ; IRQ
     79    at  ROMVARS.ideVars2+IDEVARS.bDevice,       db  DEVICE_8BIT_DUAL_PORT_XTIDE
     80    at  ROMVARS.ideVars2+IDEVARS.bIRQ,          db  0
    8081    at  ROMVARS.ideVars2+IDEVARS.drvParamsMaster+DRVPARAMS.wFlags,  db  FLG_DRVPARAMS_BLOCKMODE
    8182    at  ROMVARS.ideVars2+IDEVARS.drvParamsSlave+DRVPARAMS.wFlags,   db  FLG_DRVPARAMS_BLOCKMODE
     
    8384    at  ROMVARS.ideVars3+IDEVARS.wPort,         dw  168h            ; Controller Command Block base port
    8485    at  ROMVARS.ideVars3+IDEVARS.wPortCtrl,     dw  368h            ; Controller Control Block base port
    85     at  ROMVARS.ideVars3+IDEVARS.bBusType,      db  BUS_TYPE_16     ; Bus type
    86     at  ROMVARS.ideVars3+IDEVARS.bIRQ,          db  0               ; IRQ
     86    at  ROMVARS.ideVars3+IDEVARS.bDevice,       db  DEVICE_16BIT_ATA
     87    at  ROMVARS.ideVars3+IDEVARS.bIRQ,          db  0
    8788    at  ROMVARS.ideVars3+IDEVARS.drvParamsMaster+DRVPARAMS.wFlags,  db  FLG_DRVPARAMS_BLOCKMODE
    8889    at  ROMVARS.ideVars3+IDEVARS.drvParamsSlave+DRVPARAMS.wFlags,   db  FLG_DRVPARAMS_BLOCKMODE
     
    101102    at  ROMVARS.ideVars0+IDEVARS.wPort,         dw  300h            ; Controller Command Block base port
    102103    at  ROMVARS.ideVars0+IDEVARS.wPortCtrl,     dw  308h            ; Controller Control Block base port
    103     at  ROMVARS.ideVars0+IDEVARS.bBusType,      db  BUS_TYPE_8_DUAL ; Bus type
     104    at  ROMVARS.ideVars0+IDEVARS.bDevice,       db  DEVICE_8BIT_DUAL_PORT_XTIDE
    104105    at  ROMVARS.ideVars0+IDEVARS.bIRQ,          db  0               ; IRQ
    105106    at  ROMVARS.ideVars0+IDEVARS.drvParamsMaster+DRVPARAMS.wFlags,  db  FLG_DRVPARAMS_BLOCKMODE
     
    146147%include "DriveXlate.asm"       ; For swapping drive numbers
    147148%include "HAddress.asm"         ; For sector address translations
    148 %include "HCapacity.asm"        ; For calculating drive capacity
    149 %include "HError.asm"           ; For error checking
    150 %include "HPIO.asm"             ; For PIO transfers
    151 %include "HIRQ.asm"             ; For IRQ handling
    152 %include "HStatus.asm"          ; For reading hard disk status
    153 %include "HDrvSel.asm"          ; For selecting drive to access
    154 %include "HCommand.asm"         ; For outputting command and parameters
    155149%include "HTimer.asm"           ; For timeout and delay
    156150
     
    178172%include "AH24h_HSetBlocks.asm" ; Required by Int13h_Jump.asm
    179173%include "AH25h_HDrvID.asm"     ; Required by Int13h_Jump.asm
     174%include "Device.asm"
     175%include "Idepack.asm"
    180176
     177; IDE Device support
     178%include "IdeCommand.asm"
     179%include "IdeDPT.asm"
     180%include "IdeIO.asm"
     181%include "IdeIrq.asm"
     182%include "IdeTransfer.asm"
     183%include "IdeWait.asm"
     184%include "IdeError.asm"         ; Must be included after IdeWait.asm
     185
     186; Serial Port Device support
     187%include "SerialCommand.asm"
     188%include "SerialDPT.asm"
    181189
    182190
  • trunk/XTIDE_Universal_BIOS/Src/Strings.asm

    r143 r150  
    3636g_szSizeDual:   db  "%s%4-u.%u %ciB / %4-u.%u %ciB",LF,CR,NULL
    3737g_szCfgHeader:  db  "Addr.",SINGLE_VERTICAL,"Block",SINGLE_VERTICAL,"Bus",  SINGLE_VERTICAL,"IRQ",  SINGLE_VERTICAL,"Reset",LF,CR,NULL
    38 g_szCfgFormat:  db  "%s"   ,SINGLE_VERTICAL,"%5-u",  SINGLE_VERTICAL,"%c%2u",SINGLE_VERTICAL," %c%c",SINGLE_VERTICAL,"%5-x",  NULL
     38g_szCfgFormat:  db  "%s"   ,SINGLE_VERTICAL,"%5-u", SINGLE_VERTICAL,"%c%2u",SINGLE_VERTICAL," %c%c",SINGLE_VERTICAL,"%5-x",  NULL
    3939g_szLCHS:       db  "L-CHS",NULL
    4040g_szPCHS:       db  "P-CHS",NULL
  • trunk/XTIDE_Universal_BIOS/Src/VariablesAndDPTs/AccessDPT.asm

    r99 r150  
    66
    77;--------------------------------------------------------------------
    8 ; Returns L-CHS values from DPT.
    9 ;
     8; AccessDPT_GetDriveSelectByteToAL
     9;   Parameters:
     10;       DS:DI:  Ptr to Disk Parameter Table
     11;   Returns:
     12;       AL:     Drive Select Byte
     13;   Corrupts registers:
     14;       Nothing
     15;--------------------------------------------------------------------
     16ALIGN JUMP_ALIGN
     17AccessDPT_GetDriveSelectByteToAL:
     18    mov     al, [di+DPT.wFlags]
     19    and     al, FLG_DRVNHEAD_LBA | FLG_DRVNHEAD_DRV
     20    or      al, MASK_DRVNHEAD_SET   ; Bits set to 1 for old drives
     21    ret
     22
     23
     24;--------------------------------------------------------------------
     25; AccessDPT_GetDeviceControlByteToAL
     26;   Parameters:
     27;       DS:DI:  Ptr to Disk Parameter Table
     28;   Returns:
     29;       AL:     Device Control Byte
     30;   Corrupts registers:
     31;       Nothing
     32;--------------------------------------------------------------------
     33ALIGN JUMP_ALIGN
     34AccessDPT_GetDeviceControlByteToAL:
     35    xor     al, al
     36    test    BYTE [di+DPT.wFlags], FLG_DPT_ENABLE_IRQ
     37    jnz     SHORT .EnableDeviceIrq
     38    or      al, FLG_DEVCONTROL_nIEN ; Disable IRQ
     39.EnableDeviceIrq:
     40    ret
     41
     42
     43;--------------------------------------------------------------------
     44; AccessDPT_GetAddressingModeForWordLookToBX
     45;   Parameters:
     46;       DS:DI:  Ptr to Disk Parameter Table
     47;   Returns:
     48;       BX:     Addressing Mode (L-CHS, P-CHS, LBA28, LBA48) shifted for WORD lookup
     49;   Corrupts registers:
     50;       Nothing
     51;--------------------------------------------------------------------
     52ALIGN JUMP_ALIGN
     53AccessDPT_GetAddressingModeForWordLookToBX:
     54    mov     bl, [di+DPT.wFlags]
     55    and     bx, BYTE MASK_DPT_ADDRESSING_MODE
     56    eSHR_IM bx, ADDRESSING_MODE_FIELD_POSITION-1
     57    ret
     58
     59
     60;--------------------------------------------------------------------
    1061; AccessDPT_GetLCHSfromPCHS
    1162;   Parameters:
     
    2172AccessDPT_GetLCHSfromPCHS:
    2273    xchg    ax, cx
    23     mov     cl, [di+DPT.bShLtoP]        ; Load shift count
    24     mov     bx, [di+DPT.wPCyls]         ; Load P-CHS cylinders
    25     shr     bx, cl                      ; Shift to L-CHS cylinders
     74    mov     cl, [di+DPT.wFlags]
     75    and     cl, MASK_DPT_CHS_SHIFT_COUNT    ; Load shift count
     76    mov     bx, [di+DPT.wPchsCylinders]     ; Load P-CHS cylinders
     77    shr     bx, cl                          ; Shift to L-CHS cylinders
    2678    xchg    cx, ax
    27     mov     dx, [di+DPT.wLHeads]        ; Load L-CHS heads
    28     eMOVZX  ax, BYTE [di+DPT.bPSect]    ; Load Sectors per track
     79    eMOVZX  dx, BYTE [di+DPT.bLchsHeads]    ; Load L-CHS heads
     80    eMOVZX  ax, BYTE [di+DPT.bPchsSectors]  ; Load Sectors per track
    2981    ret
    3082
    3183
    3284;--------------------------------------------------------------------
    33 ; Tests IDEVARS flags for master or slave drive.
    34 ;
    3585; AccessDPT_TestIdeVarsFlagsForMasterOrSlaveDrive
    3686;   Parameters:
     
    63113ALIGN JUMP_ALIGN
    64114AccessDPT_GetPointerToDRVPARAMStoCSBX:
    65     eMOVZX  bx, [di+DPT.bIdeOff]        ; CS:BX points to IDEVARS
    66     test    BYTE [di+DPT.bDrvSel], FLG_IDE_DRVHD_DRV
    67     jnz     SHORT .ReturnPointerToSlaveDRVPARAMS
    68     add     bx, BYTE IDEVARS.drvParamsMaster
     115    eMOVZX  bx, [di+DPT.bIdevarsOffset]         ; CS:BX points to IDEVARS
     116    add     bx, BYTE IDEVARS.drvParamsMaster    ; CS:BX points to Master Drive DRVPARAMS
     117    test    BYTE [di+DPT.wFlags], FLG_DPT_SLAVE
     118    jz      SHORT .ReturnPointerToDRVPARAMS
     119    add     bx, BYTE DRVPARAMS_size             ; CS:BX points to Slave Drive DRVPARAMS
     120.ReturnPointerToDRVPARAMS:
    69121    ret
    70 ALIGN JUMP_ALIGN
    71 .ReturnPointerToSlaveDRVPARAMS:
    72     add     bx, BYTE IDEVARS.drvParamsSlave
    73     ret
  • trunk/XTIDE_Universal_BIOS/Src/VariablesAndDPTs/CreateDPT.asm

    r128 r150  
    2525;--------------------------------------------------------------------
    2626CreateDPT_FromAtaInformation:
    27     call    FindDPT_ForNewDrive     ; Get new DPT to DS:DI
     27    call    FindDPT_ForNewDriveToDSDI
    2828    ; Fall to .InitializeDPT
    2929
     
    3535;       CS:BP:  Ptr to IDEVARS for the controller
    3636;   Returns:
    37 ;       AX:     Zero
    38 ;   Corrupts registers:
    39 ;       Nothing
     37;       Nothing
     38;   Corrupts registers:
     39;       AX
    4040;--------------------------------------------------------------------
    4141.InitializeDPT:
    42     xor     ax, ax
    43     mov     BYTE [di+DPT.bSize], DPT_size
    44     mov     [di+DPT.wDrvNumAndFlags], ax
    45     mov     BYTE [di+DPT.bReset], MASK_RESET_ALL
    46     mov     [di+DPT.bIdeOff], bp
    47     mov     [di+DPT.bDrvSel], bh
    48     ; Fall to .StoreDriveControlByte
    49 
    50 ;--------------------------------------------------------------------
    51 ; .StoreDriveControlByte
    52 ;   Parameters:
    53 ;       AX:     Zero
     42    mov     [di+DPT.bIdevarsOffset], bp ; IDEVARS must start in first 256 bytes of ROM
     43    ; Fall to .StoreDriveSelectAndDriveControlByte
     44
     45;--------------------------------------------------------------------
     46; .StoreDriveSelectAndDriveControlByte
     47;   Parameters:
    5448;       BH:     Drive Select byte for Drive and Head Register
    5549;       DS:DI:  Ptr to Disk Parameter Table
     
    6155;       AX
    6256;--------------------------------------------------------------------
    63 .StoreDriveControlByte:
    64     cmp     BYTE [cs:bp+IDEVARS.bIRQ], al   ; Interrupts enabled?
    65     jne     SHORT .CheckHeadCount
    66     or      al, FLG_IDE_CTRL_nIEN           ; Disable interrupts
    67 .CheckHeadCount:
    68     cmp     BYTE [es:si+ATA1.wHeadCnt], 8   ; 1...8 heads?
    69     jbe     SHORT .StoreDrvCtrlByteToDPT
    70     or      al, FLG_IDE_CTRL_O8H            ; Over 8 heads (pre-ATA)
    71 .StoreDrvCtrlByteToDPT:
    72     mov     [di+DPT.bDrvCtrl], al
     57.StoreDriveSelectAndDriveControlByte:
     58    mov     al, bh
     59    and     ax, BYTE FLG_DRVNHEAD_DRV       ; AL now has Master/Slave bit
     60    cmp     [cs:bp+IDEVARS.bIRQ], ah        ; Interrupts enabled?
     61    jz      SHORT .StoreFlags               ;  If not, do not set interrupt flag
     62    or      al, FLG_DPT_ENABLE_IRQ
     63.StoreFlags:
     64    mov     [di+DPT.wFlags], ax
    7365    ; Fall to .StorePCHS
    7466
     
    7668; .StorePCHS
    7769;   Parameters:
    78 ;       AH:     Zero
    7970;       BH:     Drive Select byte for Drive and Head Register
    8071;       DS:DI:  Ptr to Disk Parameter Table
     
    9990    mov     ax, [cs:bx+DRVPARAMS.wCylinders]
    10091    mov     bx, [cs:bx+DRVPARAMS.wHeadsAndSectors]
    101     or      BYTE [di+DPT.bFlags], FLG_DPT_USERCHS
    10292
    10393.StorePCHStoDPT:
    104     mov     [di+DPT.wPCyls], ax
    105     mov     [di+DPT.wHeadsAndSectors], bx
     94    mov     [di+DPT.wPchsCylinders], ax
     95    mov     [di+DPT.wPchsHeadsAndSectors], bx
    10696    ; Fall to .StoreLCHS
    10797
     
    129119    jmp     SHORT .ShiftLoop
    130120
    131 .LimitHeadsTo255:
    132     test    bh, bh                      ; 256 heads?
    133     jz      SHORT .StoreLCHStoDPT       ;  If less, no correction needed
    134     dec     bx                          ; Limit to 255 heads since DOS does not support 256 heads
    135 .StoreLCHStoDPT:
    136     mov     [di+DPT.bShLtoP], cl
    137     mov     [di+DPT.wLHeads], bx
     121.LimitHeadsTo255:                       ; DOS does not support drives with 256 heads
     122    rcr     bh, 1                       ; Set CF if 256 heads
     123    sbb     bl, 0                       ; Decrement to 255 if 256 heads
     124    or      [di+DPT.wFlags], cl
     125    mov     [di+DPT.bLchsHeads], bl
    138126    ; Fall to .StoreAddressing
    139127
     
    146134;       Nothing
    147135;   Corrupts registers:
    148 ;       Nothing
     136;       AX, BX
    149137;--------------------------------------------------------------------
    150138.StoreAddressing:
    151     cmp     WORD [di+DPT.wPCyls], 1024      ; L-CHS possible? (no translation needed)
    152     jbe     SHORT .StoreBlockMode           ;  If so, nothing needs to be changed
    153     test    BYTE [di+DPT.bFlags], FLG_DPT_USERCHS
    154     jnz     SHORT .StorePCHSaddressing      ; Use user defined P-CHS
     139    ; Check if L-CHS addressing should be used
     140    cmp     WORD [di+DPT.wPchsCylinders], 1024  ; L-CHS possible? (no translation needed)
     141    jbe     SHORT .StoreBlockMode               ;  If so, nothing needs to be changed
     142
     143    ; Check if P-CHS addressing should be used
     144    mov     al, FLG_DRVPARAMS_USERCHS           ; User specified CHS?
     145    call    AccessDPT_TestIdeVarsFlagsForMasterOrSlaveDrive
     146    jnz     SHORT .StorePCHSaddressing
    155147    test    WORD [es:si+ATA1.wCaps], A2_wCaps_LBA
    156     jz      SHORT .StorePCHSaddressing      ; Use P-CHS since LBA not supported
     148    jz      SHORT .StorePCHSaddressing          ; Use P-CHS since LBA not supported
     149
     150    ; LBA needs to be used. Check if 48-bit LBA is supported
    157151    test    WORD [es:si+ATA6.wSetSup83], A6_wSetSup83_LBA48
    158     jz      SHORT .StoreLBA28addressing     ; Use LBA-28 since LBA-48 not supported
    159     or      BYTE [di+DPT.bFlags], ADDR_DPT_LBA48<<1
     152    jz      SHORT .StoreLBA28addressing         ; Use LBA-28 since LBA-48 not supported
     153    or      BYTE [di+DPT.wFlags], ADDRESSING_MODE_LBA48<<ADDRESSING_MODE_FIELD_POSITION
    160154.StoreLBA28addressing:
    161     or      BYTE [di+DPT.bFlags], ADDR_DPT_LBA28<<1
    162     or      BYTE [di+DPT.bDrvSel], FLG_IDE_DRVHD_LBA
     155    or      BYTE [di+DPT.wFlags], ADDRESSING_MODE_LBA28<<ADDRESSING_MODE_FIELD_POSITION
    163156    jmp     SHORT .StoreBlockMode
    164157.StorePCHSaddressing:
    165     or      BYTE [di+DPT.bFlags], ADDR_DPT_PCHS<<1
     158    or      BYTE [di+DPT.wFlags], ADDRESSING_MODE_PCHS<<ADDRESSING_MODE_FIELD_POSITION
    166159    ; Fall to .StoreBlockMode
    167160
     
    174167;       Nothing
    175168;   Corrupts registers:
    176 ;       AX
     169;       Nothing
    177170;--------------------------------------------------------------------
    178171.StoreBlockMode:
    179     mov     al, 1                       ; Minimum block size is 1 sector
    180     mov     ah, [es:si+ATA1.bBlckSize]  ; Load max block size in sectors
    181     mov     [di+DPT.wSetAndMaxBlock], ax
    182     ; Fall to .StoreEBIOSSupport
    183 
    184 ;--------------------------------------------------------------------
    185 ; .StoreEBIOSSupport
    186 ;   Parameters:
    187 ;       DS:DI:  Ptr to Disk Parameter Table
    188 ;       ES:SI:  Ptr to 512-byte ATA information read from the drive
    189 ;   Returns:
    190 ;       Nothing
    191 ;   Corrupts registers:
    192 ;       AX, BX, DX
    193 ;--------------------------------------------------------------------
    194 .StoreEBIOSSupport:
    195     test    BYTE [cs:ROMVARS.wFlags], FLG_ROMVARS_FULLMODE
    196     jz      SHORT .StoreDriveNumberAndUpdateDriveCount  ; No EBIOS support since small DPTs needed
    197 
    198     mov     bl, [di+DPT.bFlags]
    199     and     bx, BYTE MASK_DPT_ADDR                      ; Addressing mode
    200     jmp     [cs:bx+.rgwAddrJmp]                         ; Jump to handle addressing mode
    201 .rgwAddrJmp:
    202     dw      .StoreDriveNumberAndUpdateDriveCount        ; ADDR_DPT_LCHS
    203     dw      .StoreDriveNumberAndUpdateDriveCount        ; ADDR_DPT_PCHS
    204     dw      .SupportForLBA28                            ; ADDR_DPT_LBA28
    205     dw      .SupportForLBA48                            ; ADDR_DPT_LBA48
    206 
    207 .SupportForLBA28:
    208     sub     BYTE [di+DPT.bSize], 2      ; Only 4 bytes for sector count
    209 .SupportForLBA48:
    210     add     BYTE [di+DPT.bSize], EBDPT_size - DPT_size
    211     or      BYTE [di+DPT.bFlags], FLG_DPT_EBIOS
    212     call    AtaID_GetTotalSectorCount
    213     mov     [di+EBDPT.twCapacity], ax
    214     mov     [di+EBDPT.twCapacity+2], dx
    215     mov     [di+EBDPT.twCapacity+4], bx
     172    cmp     BYTE [es:si+ATA1.bBlckSize], 1  ; Max block size in sectors
     173    jbe     SHORT .BlockModeTransfersNotSupported
     174    or      WORD [di+DPT.wFlags], FLG_DPT_BLOCK_MODE_SUPPORTED
     175.BlockModeTransfersNotSupported:
     176    ; Fall to .StoreDeviceSpecificParameters
     177
     178;--------------------------------------------------------------------
     179; .StoreDeviceSpecificParameters
     180;   Parameters:
     181;       DS:DI:  Ptr to Disk Parameter Table
     182;       ES:SI:  Ptr to 512-byte ATA information read from the drive
     183;   Returns:
     184;       Nothing
     185;   Corrupts registers:
     186;       AX, BX, CX, DX
     187;--------------------------------------------------------------------
     188.StoreDeviceSpecificParameters:
     189    call    Device_FinalizeDPT
    216190    ; Fall to .StoreDriveNumberAndUpdateDriveCount
    217191
     
    230204;--------------------------------------------------------------------
    231205.StoreDriveNumberAndUpdateDriveCount:
    232     ; Make sure that more drives can be accepted
    233     mov     dl, [es:BDA.bHDCount]   ; Load number of hard disks
    234     test    dl, dl                  ; Hard disks at maximum?
    235     stc                             ; Assume error
    236     js      SHORT .TooManyDrives    ;  If so, return
    237 
    238     ; Store drive number to DPT
    239     or      dl, 80h                 ; Set bit 7 since hard disk
    240     mov     [di+DPT.bDrvNum], dl    ; Store drive number
    241 
    242     ; Update BDA and RAMVARS
    243     inc     BYTE [es:BDA.bHDCount]  ; Increment drive count to BDA
    244     call    RamVars_IncrementHardDiskCount
     206    mov     dl, [es:BDA.bHDCount]
     207    or      dl, 80h                     ; Set bit 7 since hard disk
     208
     209    inc     BYTE [RAMVARS.bDrvCnt]      ; Increment drive count to RAMVARS
     210    inc     BYTE [es:BDA.bHDCount]      ; Increment drive count to BDA
     211
     212    cmp     BYTE [RAMVARS.bFirstDrv], 0 ; First drive set?
     213    ja      SHORT .AllDone              ;  If so, return
     214    mov     [RAMVARS.bFirstDrv], dl     ; Store first drive number
     215.AllDone:
    245216    clc
    246 .TooManyDrives:
    247217    ret
  • trunk/XTIDE_Universal_BIOS/Src/VariablesAndDPTs/FindDPT.asm

    r3 r150  
    1 ; File name     :   FindDPT.asm
    2 ; Project name  :   IDE BIOS
    3 ; Created date  :   14.3.2010
    4 ; Last update   :   12.4.2010
    5 ; Author        :   Tomi Tilli
     1; Project name  :   XTIDE Universal BIOS
    62; Description   :   Functions for finding Disk Parameter Table.
    73
     
    128; Finds pointer to first unused Disk Parameter Table.
    139;
    14 ; FindDPT_ForNewDrive
     10; FindDPT_ForNewDriveToDSDI
    1511;   Parameters:
    1612;       DS:     RAMVARS segment
     
    1814;       DS:DI:  Ptr to first unused DPT
    1915;   Corrupts registers:
    20 ;       Nothing
     16;       DL
    2117;--------------------------------------------------------------------
    2218ALIGN JUMP_ALIGN
    23 FindDPT_ForNewDrive:
    24     push    si
    25     mov     si, FindDPT_ReturnWrongDPT
    26     jmp     SHORT FindDPT_StartIterationAndReturnAfterDone
    27 
    28 
    29 ;--------------------------------------------------------------------
    30 ; Finds Disk Parameter Table for
    31 ; Master or Slave drive at wanted port.
    32 ;
    33 ; FindDPT_ForIdeSlaveAtPort
    34 ; FindDPT_ForIdeMasterAtPort
    35 ;   Parameters:
    36 ;       DX:     IDE Base Port address
    37 ;       DS:     RAMVARS segment
    38 ;   Returns:
    39 ;       DL:     Drive number (if DPT found)
    40 ;       DS:DI:  Ptr to DPT
    41 ;       CF:     Set if wanted DPT found
    42 ;               Cleared if DPT not found
    43 ;   Corrupts registers:
    44 ;       Nothing
    45 ;--------------------------------------------------------------------
    46 ALIGN JUMP_ALIGN
    47 FindDPT_ForIdeSlaveAtPort:
    48     push    si
    49     mov     si, FindDPT_IterateToSlaveAtPortCallback
    50     jmp     SHORT FindDPT_StartIterationAndReturnAfterDone
    51 
    52 ALIGN JUMP_ALIGN
    53 FindDPT_ForIdeMasterAtPort:
    54     push    si
    55     mov     si, FindDPT_IterateToMasterAtPortCallback
    56     jmp     SHORT FindDPT_StartIterationAndReturnAfterDone
    57 
    58 ;--------------------------------------------------------------------
    59 ; Iteration callback for finding DPT using
    60 ; IDE base port for Master or Slave drive.
    61 ;
    62 ; FindDPT_IterateToSlaveAtPortCallback
    63 ; FindDPT_IterateToMasterAtPortCallback
    64 ;   Parameters:
    65 ;       DX:     IDE Base Port address
    66 ;       DS:DI:  Ptr to DPT to examine
    67 ;   Returns:
    68 ;       DL:     Drive number if correct DPT
    69 ;       CF:     Set if wanted DPT found
    70 ;               Cleared if wrong DPT
    71 ;   Corrupts registers:
    72 ;       Nothing
    73 ;--------------------------------------------------------------------
    74 ALIGN JUMP_ALIGN
    75 FindDPT_IterateToSlaveAtPortCallback:
    76     test    BYTE [di+DPT.bDrvSel], FLG_IDE_DRVHD_DRV
    77     jnz     SHORT FindDPT_IterateToMasterOrSlaveAtPortCallback
    78     jmp     SHORT FindDPT_ReturnWrongDPT    ; Return if master drive
    79 
    80 ALIGN JUMP_ALIGN
    81 FindDPT_IterateToMasterAtPortCallback:
    82     test    BYTE [di+DPT.bDrvSel], FLG_IDE_DRVHD_DRV
    83     jnz     SHORT FindDPT_ReturnWrongDPT    ; Return if slave drive
    84 
    85     ; If BIOS partitioned, ignore all but first partition
    86 ALIGN JUMP_ALIGN
    87 FindDPT_IterateToMasterOrSlaveAtPortCallback:
    88     test    BYTE [di+DPT.bFlags], FLG_DPT_PARTITION
    89     jz      SHORT .CompareBasePortAddress
    90     test    BYTE [di+DPT.bFlags], FLG_DPT_FIRSTPART
    91     jz      SHORT FindDPT_ReturnWrongDPT
    92 ALIGN JUMP_ALIGN
    93 .CompareBasePortAddress:
    94     push    bx
    95     eMOVZX  bx, BYTE [di+DPT.bIdeOff]       ; CS:BX now points to IDEVARS
    96     cmp     dx, [cs:bx+IDEVARS.wPort]       ; Wanted port?
    97     pop     bx
    98     jne     SHORT FindDPT_ReturnWrongDPT
    99     mov     dl, [di+DPT.bDrvNum]            ; Load drive number
    100     stc                                     ; Set CF since wanted DPT
    101     ret
     19FindDPT_ForNewDriveToDSDI:
     20    mov     dl, [RAMVARS.bFirstDrv]
     21    add     dl, [RAMVARS.bDrvCnt]
     22    ; Fall to FindDPT_ForDriveNumber
    10223
    10324
     
    11233;   Returns:
    11334;       DS:DI:  Ptr to DPT
    114 ;       CF:     Set if wanted DPT found
    115 ;               Cleared if DPT not found
    11635;   Corrupts registers:
    11736;       Nothing
     
    11938ALIGN JUMP_ALIGN
    12039FindDPT_ForDriveNumber:
    121     push    si
    122     mov     si, FindDPT_IterateToDriveNumberCallback
    123 FindDPT_StartIterationAndReturnAfterDone:
    124     call    FindDPT_IterateAllDPTs
    125     pop     si
     40    push    dx
     41    push    ax
     42
     43    mov     al, LARGEST_DPT_SIZE
     44    sub     dl, [RAMVARS.bFirstDrv]
     45    mul     dl
     46    add     ax, BYTE RAMVARS_size
     47    xchg    di, ax
     48
     49    pop     ax
     50    pop     dx
    12651    ret
    12752
     53
    12854;--------------------------------------------------------------------
    129 ; Iteration callback for finding DPT for drive number.
     55; Finds Disk Parameter Table for
     56; Master or Slave drive at wanted port.
    13057;
    131 ; FindDPT_IterateToDriveNumberCallback
     58; FindDPT_ToDSDIForIdeMasterAtPortDX
     59; FindDPT_ToDSDIForIdeSlaveAtPortDX
    13260;   Parameters:
    133 ;       DL:     Drive number to search for
     61;       DX:     IDE Base Port address
     62;       DS:     RAMVARS segment
     63;   Returns:
     64;       DL:     Drive number (if DPT found)
     65;       DS:DI:  Ptr to DPT
     66;       CF:     Set if wanted DPT found
     67;               Cleared if DPT not found
     68;   Corrupts registers:
     69;       SI
     70;--------------------------------------------------------------------
     71ALIGN JUMP_ALIGN
     72FindDPT_ToDSDIForIdeMasterAtPortDX:
     73    mov     si, FindDPT_IterateToMasterAtPortCallback
     74    jmp     SHORT IterateAllDPTs
     75
     76ALIGN JUMP_ALIGN
     77FindDPT_ToDSDIForIdeSlaveAtPortDX:
     78    mov     si, FindDPT_IterateToSlaveAtPortCallback
     79    jmp     SHORT IterateAllDPTs
     80
     81;--------------------------------------------------------------------
     82; Iteration callback for finding DPT using
     83; IDE base port for Master or Slave drive.
     84;
     85; FindDPT_IterateToSlaveAtPortCallback
     86; FindDPT_IterateToMasterAtPortCallback
     87;   Parameters:
     88;       CH:     Drive number
     89;       DX:     IDE Base Port address
    13490;       DS:DI:  Ptr to DPT to examine
    13591;   Returns:
     92;       DL:     Drive number if correct DPT
    13693;       CF:     Set if wanted DPT found
    13794;               Cleared if wrong DPT
     
    14097;--------------------------------------------------------------------
    14198ALIGN JUMP_ALIGN
    142 FindDPT_IterateToDriveNumberCallback:
    143     cmp     dl, [di+DPT.bDrvNum]            ; Wanted DPT found?
    144     je      SHORT FindDPT_RightDriveNumber  ;  If so, return
    145 FindDPT_ReturnWrongDPT:
    146     clc                                     ; Clear CF since wrong DPT
     99FindDPT_IterateToSlaveAtPortCallback:
     100    test    BYTE [di+DPT.wFlags], FLG_DPT_SLAVE ; Clears CF
     101    jnz     SHORT CompareBasePortAddress
     102    ret     ; Wrong DPT
     103
     104ALIGN JUMP_ALIGN
     105FindDPT_IterateToMasterAtPortCallback:
     106    test    BYTE [di+DPT.wFlags], FLG_DPT_SLAVE
     107    jnz     SHORT ReturnWrongDPT                ; Return if slave drive
     108
     109CompareBasePortAddress:
     110    push    bx
     111    eMOVZX  bx, BYTE [di+DPT.bIdevarsOffset]    ; CS:BX now points to IDEVARS
     112    cmp     dx, [cs:bx+IDEVARS.wPort]           ; Wanted port?
     113    pop     bx
     114    jne     SHORT ReturnWrongDPT
     115    mov     dl, ch                              ; Return drive number in DL
     116    stc                                         ; Set CF since wanted DPT
    147117    ret
    148 ALIGN JUMP_ALIGN
    149 FindDPT_RightDriveNumber:
    150     push    bx
    151     eMOVZX  bx, BYTE [di+DPT.bIdeOff]       ; CS:BX now points to IDEVARS
    152     mov     bx, [cs:bx+IDEVARS.wPort]       ; Load IDE Base Port address...
    153     mov     [RAMVARS.wIdeBase], bx          ; ...and store it to RAMVARS
    154     pop     bx
    155     stc
     118ReturnWrongDPT:
     119    clc                                         ; Clear CF since wrong DPT
    156120    ret
    157121
     
    160124; Iterates all Disk Parameter Tables.
    161125;
    162 ; FindDPT_IterateAllDPTs
     126; IterateAllDPTs
    163127;   Parameters:
    164128;       BX,DX:  Parameters to callback function
     
    170134;               Cleared if DPT not found
    171135;   Corrupts registers:
    172 ;       Nothing, unless corrupted by callback function
     136;       Nothing unless corrupted by callback function
    173137;--------------------------------------------------------------------
    174138ALIGN JUMP_ALIGN
    175 FindDPT_IterateAllDPTs:
    176     push    ax
     139IterateAllDPTs:
    177140    push    cx
     141    mov     cx, [RAMVARS.wDrvCntAndFirst]
     142    jcxz    .AllDptsIterated            ; Return if no drives
    178143    call    FindDPT_PointToFirstDPT     ; Point DS:DI to first DPT
    179     eMOVZX  cx, BYTE [RAMVARS.bDrvCnt]  ; Load number of drives
    180     xor     ax, ax                      ; Zero AX for DPT size and clear CF
    181     jcxz    .Return                     ; Return if no drives
    182144ALIGN JUMP_ALIGN
    183145.LoopWhileDPTsLeft:
    184146    call    si                          ; Is wanted DPT?
    185     jc      SHORT .Return               ;  If so, return
    186     mov     al, [di+DPT.bSize]          ; Load DPT size to AX
    187     add     di, ax                      ; Point to next DPT
    188     loop    .LoopWhileDPTsLeft          ; Check next DPT
     147    jc      SHORT .AllDptsIterated      ;  If so, return
     148    inc     ch                          ; Increment drive number
     149    add     di, BYTE LARGEST_DPT_SIZE   ; Point to next DPT
     150    dec     cl                          ; Decrement drives left
     151    jnz     SHORT .LoopWhileDPTsLeft
    189152    clc                                 ; Clear CF since DPT not found
    190153ALIGN JUMP_ALIGN
    191 .Return:
     154.AllDptsIterated:
    192155    pop     cx
    193     pop     ax
    194156    ret
    195157
     
    209171FindDPT_PointToFirstDPT:
    210172    mov     di, RAMVARS_size
    211     test    BYTE [cs:ROMVARS.wFlags], FLG_ROMVARS_FULLMODE
    212     jz      SHORT .Return                           ; RAMVARS used (top of interrupt vectors)
    213     add     di, BYTE FULLRAMVARS_size-RAMVARS_size  ; FULLRAMVARS used (top of base memory)
    214 ALIGN JUMP_ALIGN
    215 .Return:
    216173    ret
  • trunk/XTIDE_Universal_BIOS/Src/VariablesAndDPTs/RamVars.asm

    r148 r150  
    4040    eSHL_IM ax, 6                       ; Segment to first stolen kB (*=40h)
    4141    mov     ds, ax
    42     mov     WORD [FULLRAMVARS.wSign], W_SIGN_FULLRAMVARS
    43     ; Fall to .InitializeRamvarsFromDS
     42    mov     WORD [RAMVARS.wSignature], RAMVARS_SIGNATURE
     43    ; Fall to .InitializeRamvars
    4444
    4545;--------------------------------------------------------------------
     
    5959    pop     es
    6060    call    Memory_ZeroESDIwithSizeInCX
     61    mov     WORD [RAMVARS.wSignature], RAMVARS_SIGNATURE
    6162    ; Fall to .InitializeDriveTranslationAndReturn
    6263
     
    9293    test    BYTE [cs:ROMVARS.wFlags], FLG_ROMVARS_FULLMODE
    9394    jnz     SHORT .GetStolenSegmentToDS
    94     mov     di, SEGMENT_RAMVARS_TOP_OF_INTERRUPT_VECTORS
     95    mov     di, LITE_MODE_RAMVARS_SEGMENT
    9596    mov     ds, di
    9697    ret
     
    105106    mov     ds, di                  ; EBDA segment to DS
    106107    add     di, BYTE 64             ; DI to next stolen kB
    107     cmp     WORD [FULLRAMVARS.wSign], W_SIGN_FULLRAMVARS
     108    cmp     WORD [RAMVARS.wSignature], RAMVARS_SIGNATURE
    108109    jne     SHORT .LoopStolenKBs    ; Loop until sign found (always found eventually)
    109110    ret
     
    167168
    168169;--------------------------------------------------------------------
    169 ; RamVars_IncrementHardDiskCount
    170 ;   Parameters:
    171 ;       DL:     Drive number for new drive
    172 ;       DS:     RAMVARS segment
    173 ;   Returns:
    174 ;       Nothing
    175 ;   Corrupts registers:
    176 ;       Nothing
    177 ;--------------------------------------------------------------------
    178 RamVars_IncrementHardDiskCount:
    179     inc     BYTE [RAMVARS.bDrvCnt]      ; Increment drive count to RAMVARS
    180     cmp     BYTE [RAMVARS.bFirstDrv], 0 ; First drive set?
    181     ja      SHORT .Return               ;  If so, return
    182     mov     [RAMVARS.bFirstDrv], dl     ; Store first drive number
    183 .Return:
    184     ret
    185 
    186 
    187 ;--------------------------------------------------------------------
    188170; RamVars_GetHardDiskCountFromBDAtoCX
    189171;   Parameters:
  • trunk/XTIDE_Universal_BIOS/makefile

    r145 r150  
    3939HEADERS += Src/Handlers/Int13h/
    4040HEADERS += Src/Handlers/Int13h/Common/
     41HEADERS += Src/Device/
     42HEADERS += Src/Device/IDE/
     43HEADERS += Src/Device/Serial/
    4144HEADERS += Src/Initialization/
    4245HEADERS += Src/Libraries/
Note: See TracChangeset for help on using the changeset viewer.