📄 wdrminit.asm
字号:
;------------------------------------------------------------------------------
;** Phase 4/B/12 (Three passes through here)
WD_VD_Do_Read_Now:
push es
mov ax, ds
mov es, ax
mov bx, OFFSET Int13_Buffer
mov ax, 0201h ; Read one sector
mov cx, [bp.Test_Cyl_Num]
xchg ch, cl
shl cl, 6
or cl, BYTE PTR [bp.Test_Sector_Num]
mov dl, [bp.Test_Drive_Number] ; DL = Drive number
mov dh, BYTE PTR [bp.Test_Head_Num]
pushf
cli
call [ROM_BIOS_Int13_Vec]
pop es ; ES:DI points to drive params!
mov al, ah ; Put value in AL for macro
Check_Invalid jc
;------------------------------------------------------------------------------
;
; The thing worked! Now check all the I/O ports to make sure they look
; the way we want them to.
;
;------------------------------------------------------------------------------
;** Phase 5/C/13
mov dx, WDIO_Def_Base_Port+WDIO_Error_Off
in al, dx ; Read the error status
test al, al ; Non-zero is no good
Check_Invalid jnz
;** Phase 6/D/14
inc dx
IO_Delay
IO_Delay
in al, dx ; Read the sector count
test al, al ; Non-zero is no good
Check_Invalid jnz
;** Phase 7/E/15
inc dx
IO_Delay
IO_Delay
in al, dx ; Read the sector number
cmp al, BYTE PTR [bp.Test_Sector_Num];Q: Is sector number right?
Check_Invalid jne ; N: Die! Die! Die!
;** Phase 8/F/16
inc dx
IO_Delay
IO_Delay
in al, dx ; Read low cyl number
mov ah, al
inc dx
IO_Delay
IO_Delay
in al, dx ; Read high cyl number
xchg al, ah
cmp ax, [bp.Test_Cyl_Num] ; Q: Cyl number correct?
Check_Invalid jnz ; N: Wrong track
;** Phase 9/10/17
inc dx
mov al, [bp.Test_Drive_Number] ; Get drive #
and ax, 1
shl ax, 12 ; Move bit to proper position
IO_Delay
IO_Delay
in al, dx
xor al, ah ; Drive bit should be 0.
xor al, BYTE PTR [bp.Test_Head_Num] ; Should make head # 0
cmp al, 10100000b ; Q: Head 0, 512 byte sectors?
Check_Invalid jne ; N: Error
;** Phase A/11/18
inc dx
IO_Delay
IO_Delay
in al, dx ; Read status
mov ah, al ; Preserve real status in case
and ah, NOT (WDStat_ECC_Corrected OR WDStat_Index) ; of error we
cmp ah, WDStat_Ready OR WDStat_Seek_Complete ; will get good info
Check_Invalid jne
;------------------------------------------------------------------------------
;
; Wowsa! All of the port status looks correct. Now for the big, grand-
; pooba test -- Actually try to read some data by directly programming
; the controller. This is pretty silly polling code, but it dosen't really
; matter.
;
;------------------------------------------------------------------------------
IO_Delay
IO_Delay
in al, 0A1h
or al, 01000000b
IO_Delay
IO_Delay
out 0A1h, al
mov dx, WDIO_Def_Base_Port+WDIO_Drive_Control_Off
mov al, es:[di.FDPT_Drive_Control]
IO_Delay
IO_Delay
out dx, al
mov ax, es:[di.FDPT_Write_Precom_Cyl]
cmp ax, -1
jne SHORT WD_VD_Set_Precom
xor ax, ax
WD_VD_Set_Precom:
shr ax, 2
mov dx, WDIO_Def_Base_Port+WDIO_Precomp_Off
IO_Delay
IO_Delay
out dx, al
inc dx
mov al, 1
IO_Delay
IO_Delay
out dx, al ; Sector count = 1
inc dx
mov ax, [bp.Test_Sector_Num]
IO_Delay
IO_Delay
out dx, al ; Sector number
inc dx
mov ax, [bp.Test_Cyl_Num]
IO_Delay
IO_Delay
out dx, al ; Low byte of cylinder
inc dx
mov al, ah
IO_Delay
IO_Delay
out dx, al ; High byte
mov al, 10100000b ; Head 0, drive 0
test [bp.Test_Drive_Number], 1 ; Q: Drive 1?
jz SHORT WD_VD_Prog_Head
mov al, 10110000b ; Head 0, drive 1
WD_VD_Prog_Head:
or al, BYTE PTR [bp.Test_Head_Num]
inc dx
IO_Delay
IO_Delay
out dx, al
inc dx
mov al, 20h
IO_Delay
IO_Delay
out dx, al ; Send a read to Mr. Ctrl
;------------------------------------------------------------------------------
;
; The command has been sent. Now wait for the command to complete.
; Check to see whether or not we have already detected that we CANNOT
; use the ALT status register. If we detect this, we don't try again.
;
;------------------------------------------------------------------------------
cmp [bp.Test_Alt_Status_Flag], 0
je SHORT WD_VD_Try_Normal_Status ; Nope, must use NORMAL status
mov ax, 40h
mov es, ax
mov cx, 18*3/4 ; 3/4 second time-out
mov dx, WDIO_Def_Base_Port + WDIO_Alt_Stat_Off
WD_VD_One_More_Tick:
mov bl, BYTE PTR es:[6Ch] ; BL = Low byte of tick count
WD_VD_Loop_Til_Done:
IO_Delay
IO_Delay
in al, dx ; AL = Status
test al, WDStat_Busy ; Q: Controller busy?
jz SHORT WD_VD_No_Longer_Busy ; N: Read the data!
; Y: Keep polling
WD_VD_Not_Really_Done:
cmp bl, BYTE PTR es:[6Ch] ; Q: Has time changed?
je SHORT WD_VD_Loop_Til_Done ; N: Don't time-out
loop WD_VD_One_More_Tick ; else dec CX count
jmp SHORT WD_VD_Try_Normal_Status ; We timed out!!
;------------------------------------------------------------------------------
;
; The controller is no longer busy. Now make sure the status looks right.
; (No error, data request set)
; This test is kind of strange, but it is important. Apparently on some
; controllers the controller will go to the not busy state BEFORE setting
; the DRQ bit. We'll just keep looping until we see not busy AND DRQ set.
;
; If the ALT status register doesn't look good, we'll try it again with
; the normal status register.
;
;------------------------------------------------------------------------------
WD_VD_No_Longer_Busy:
test al, WDStat_Error ; Q: Error?
jnz SHORT WD_VD_Try_Normal_Status ; Y: Try the normal status reg
test al, WDStat_DRQ ; Q: Data request set?
jz SHORT WD_VD_Not_Really_Done ; N: Keep looking for it
;** Once we get here, we're OK using the ALT status register
mov dx, WDIO_Def_Base_Port + WDIO_Status_Off
IO_Delay
IO_Delay
in al, dx ; Clear IRQ by reading status
jmp SHORT WD_VD_Status_OK ; Y: Things look happy
;------------------------------------------------------------------------------
;
; If we timed out or if we encountered a strange register configuration,
; we need to check the normal status register because we've only been
; looking at the alternate up to this point. We will flag what the final
; decision between normal and alternate register is. If neither one is
; right, we bail out.
;
;------------------------------------------------------------------------------
WD_VD_Try_Normal_Status:
mov [bp.Test_Alt_Status_Flag], 0
mov cx, 18*3/4 ; Reset 3/4 second time-out
mov dx, WDIO_Def_Base_Port + WDIO_Status_Off
WD_VD_N_One_More_Tick:
mov bl, BYTE PTR es:[6Ch] ; BL = Low byte of tick count
WD_VD_N_Loop_Til_Done:
IO_Delay
IO_Delay
in al, dx ; AL = Status
test al, WDStat_Busy ; Q: Controller busy?
jz SHORT WD_VD_N_No_Longer_Busy ; N: Read the data!
; Y: Keep polling
WD_VD_N_Not_Really_Done:
cmp bl, BYTE PTR es:[6Ch] ; Q: Has time changed?
je SHORT WD_VD_N_Loop_Til_Done ; N: Don't time-out
loop WD_VD_N_One_More_Tick ; else dec CX count
Check_Fatal_Error jmp, FATAL_TIME_OUT ; Timeout!!!
;------------------------------------------------------------------------------
;
; As with the ALT status register, we get here when the NORMAL status
; register is no longer busy. We have to check to see that there was
; no reported error, and that the DREQ bit is set. If we pass these
; tests, we're still OK (even though the ALT reg failed) and we just
; flag to always use the normal status register.
;
;------------------------------------------------------------------------------
WD_VD_N_No_Longer_Busy:
test al, WDStat_Error ; Q: Error?
Check_Fatal_Error jnz, FATAL_BAD_STATUS ; Y: Die!
test al, WDStat_DRQ ; Q: Data request set?
jz WD_VD_N_Not_Really_Done ; N: Keep looping!
; Y: We look happy now
;------------------------------------------------------------------------------
;
; Looks good. Now read the data and compare it to what the BIOS gave us back
;
;------------------------------------------------------------------------------
WD_VD_Status_OK:
mov ax, ds
mov es, ax
mov di, OFFSET My_Read_Buffer
mov cx, 100h
cld
mov dx, WDIO_Def_Base_Port+WDIO_Data_Off
IO_Delay
IO_Delay
rep insw
mov si, OFFSET Int13_Buffer
mov di, OFFSET My_Read_Buffer
mov cx, 80h
cld
rep cmpsd
Check_Fatal_Error jne, FATAL_DATA_BAD_COMPARE
;------------------------------------------------------------------------------
;
; It worked! Everything is OK. No re-enable interrupts for the drive.
;
;------------------------------------------------------------------------------
in al, 0A1h
and al, NOT 01000000b
IO_Delay
IO_Delay
out 0A1h, al
;------------------------------------------------------------------------------
;
; Step to the next phase of the test. First we will re-load ES:DI to point
; to the drive parameter table.
;
;------------------------------------------------------------------------------
les di, DWORD PTR [bp.Test_Param_Off]
inc [bp.Test_Loop_Phase]
cmp [bp.Test_Loop_Phase], 3
jb WD_VD_Do_Next_Test
;------------------------------------------------------------------------------
;
; This is a valid drive. Return with carry clear.
;
;------------------------------------------------------------------------------
mov bx, [bp.Test_Alt_Status_Flag]
add sp, SIZE Test_Stack_Frame
pop bp
pop es
clc
ret
;------------------------------------------------------------------------------
;
; This is NOT a valid drive.
;
;------------------------------------------------------------------------------
WD_VD_Invalid:
xor bx, bx ;Clear use bits
mov cx, [bp.Test_Phase]
mov ch, al
add sp, SIZE Test_Stack_Frame
pop bp
pop es
stc
ret
EndProc WDCtrl_Validate_Drive
;******************************************************************************
;
; WD_RMI_Int_13h_Hook
;
; DESCRIPTION:
; This stub procedure is only hooked into the Int 13h chain for a
; very short period of time. However, if it is called, it will cause
; a fatal error. Disk cache programs that do "lazy writes" may wake
; up on a timer interrupt and attempt to write out a sector. In this
; case, we will display an error message and hang the machine.
;
; ENTRY:
; Who cares!
;
; EXIT:
; Never
;
; USES:
; Anything it wants
;
;==============================================================================
BeginProc WD_RMI_Int_13h_Hook
IFDEF SETUP
mov ax, DGROUP ; Set up DS, ES to our data segment before
mov ds, ax ; calling the display error routine.
mov es, ax
mov ss, ax
mov sp, 0FFFEh
mov ax, ERR_WDCTRL_BAD_SOFTWARE
push ax
call _WDCtrlHangError
pop ax
ELSE
mov ah, 9
mov dx, OFFSET WD_Incompatible_Sw_Msg
int 21h
ENDIF
jmp $
EndProc WD_RMI_Int_13h_Hook
IFNDEF SETUP
;******************************************************************************
;
; WD_RMI_Get_Env_String
;
; DESCRIPTION:
; Tries to find a given string in the environment. If the resulting
; string starts with 'Y', 'y', 'T', 't', or '1', returns nonzero in
; AX
;
; ENTRY:
; ES points to environment
; SI is string to match
; CX is length of string to match
;
; EXIT:
; AX is nonzero iff string is found and starts with chars above.
;
; USES:
; Does not trash ES or other seg regs. Don't assume anything else!
;
;==============================================================================
BeginProc WD_RMI_Get_Env_String
xor di, di ;Environment always at zero offset
mov dx, si ;Save string start in DX
mov bx, cx ;Save string len in BX
WD_GES_Try_Another_String:
mov si, dx ;Point to start of compare string
mov cx, bx ;Restore string len match
cld
push di ;Save current position in env seg
repe cmpsb
mov al, es:[di] ;Get the first char after '='
pop di
jne SHORT WD_GES_Try_Next_Env_Str
cmp al, '1'
je SHORT WD_GES_Exit ;Return nonzero
and al, NOT ('a'-'A') ;Convert to uppercase
cmp al, 'Y'
je SHORT WD_GES_Exit ;Return nonzero
cmp al, 'T'
je SHORT WD_GES_Exit ;Return nonzero
xor ax, ax ;Return zero, string found but bad char
jmp SHORT WD_GES_Exit
WD_GES_Try_Next_Env_Str:
xor cx, cx
mov ax, cx
dec cx
repne scasb
cmp es:[di], al ;End of environment?
jne WD_GES_Try_Another_String ;No, try next string
;Return zero, string not found
WD_GES_Exit:
ret
EndProc WD_RMI_Get_Env_String
ENDIF
IFDEF SETUP
FASTDISK ENDS
ELSE
VxD_REAL_INIT_ENDS
ENDIF
IFDEF SETUP
EndFile MACRO EntryPoint
END
ENDM
ELSE
EndFile MACRO EntryPoint
END EntryPoint
ENDM
ENDIF
EndFile WDCtrl_Real_Mode_Init
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -