📄 usbbb.asm
字号:
;
; Description: This function checks for non-compliant USB devices by
; by comparing the device's vendor and device id with
; the non-compliant device table list and updates the
; data structures appropriately to support the device.
;
; Input: DI Pointer to the descriptor structure
; CX End offset of the device descriptor
;
; Output: None
;
; Modified: Nothing
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBBB_CheckNonCompliantDevice PROC NEAR SYSCALL PUBLIC
push ax
push si
; Get the current device's vendor & device ID
mov eax, DWORD PTR CurrentDevice.wVendorID
; Search the bad device table to get the structure for this device
mov si, OFFSET CS:USBBadDeviceTable
UBCNCD_Loop:
cmp si, OFFSET CS:USBBadDeviceTableEnd
jae UBCNCD_Exit ; NC, ok configure device
cmp eax, DWORD PTR CS:[si] ; Compare with table entry
je UBCNCD_DeviceFound
; Prepare to check next device
add si, SIZE stBadUSBDevice
jmp SHORT UBCNCD_Loop
UBCNCD_DeviceFound:
; Save the incompatibility flag into device info structure
mov ax, (stBadUSBDevice PTR CS:[si]).wFlags
mov CurrentDevice.wIncompatFlags, ax
; Check which fields to update in the interface descriptor
; Check for base class field
cmp (stBadUSBDevice PTR CS:[si]).bBaseClass, 0
jz UBCNCD_CheckSubClass
; Update base class field in the interface descriptor
mov al, (stBadUSBDevice PTR CS:[si]).bBaseClass
mov (InterfaceDescriptor PTR [di]).bBaseClass, al
UBCNCD_CheckSubClass:
; Check for sub class field
cmp (stBadUSBDevice PTR CS:[si]).bSubClass, 0
jz UBCNCD_CheckProtocol
; Update sub class field in the interface descriptor
mov al, (stBadUSBDevice PTR CS:[si]).bSubClass
mov (InterfaceDescriptor PTR [di]).bSubClass, al
UBCNCD_CheckProtocol:
; Check for protocol field
cmp (stBadUSBDevice PTR CS:[si]).bProtocol, 0
jz UBCNCD_Exit
; Update protocol field in the interface descriptor
mov al, (stBadUSBDevice PTR CS:[si]).bProtocol
mov (InterfaceDescriptor PTR [di]).bProtocol, al
UBCNCD_Exit:
pop si
pop ax
ret
USBBB_CheckNonCompliantDevice ENDP
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure: USBBB_CopyDeviceRequest
;
; Description: This function will copy the device request related parameter
; into the control setup data structure
;
; Input: DS USB data area
; SI Pointer to device info structure
;
; Output: None
;
; Modified: Nothing
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBBB_CopyDeviceRequest PROC NEAR PUBLIC
pusha
push es
push ds
pop es
add si, OFFSET DeviceInfo.CntrlXfer.wRequest
mov cx, SIZE DeviceRequest
rep movsb
pop es
popa
ret
USBBB_CopyDeviceRequest ENDP
IF MKF_USB_BB_DEV_KBD
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure: USBBB_ProcessKeyboardData
;
; Description: This function will parses through the data obtained from
; the USB keyboard for the valid key press combinations and
; set flags appropriately
;
; Input: DS USB data area
; DI Pointer to the data read from the USB keyboard
;
; Output: None
;
; Modified: Nothing
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBBB_ProcessKeyboardData PROC NEAR PUBLIC
pusha
; Check for the modifier
; BIT 0 - Left Control
; BIT 1 - Left Shift
; BIT 2 - Left Alt
; BIT 3 - Left GUI
; BIT 4 - Right Control
; BIT 5 - Right Shift
; BIT 6 - Right ALT
; BIT 7 - Right GUI
mov si, di
add di, 2 ; Point to key code
; Scan input buffer for the defined hot keys
mov cx, 3
mov bx, OFFSET USBKeyboardScanCodeTable
UBPKD_CheckScanCode:
mov al, BYTE PTR CS:[bx+1] ; read next MKF_USB_SCAN_x
or al, al ; zero?
jz UBPKD_NextScanCode ; yes - check next scan code
push cx
push di
mov cx, 6
repnz scasb ; scan code is found?
pop di
pop cx
jnz UBPKD_NextScanCode
; Scan code matches. Check for status bits
mov al, BYTE PTR CS:[bx]
test al, BYTE PTR [si]
jz UBPKD_NextScanCode
; Key combination matches update flag
push ds
push RUN_CSEG
pop ds
ASSUME ds:RUN_CSEG
mov al, BYTE PTR CS:[bx+2]
mov ds:boot_block_flag, al
pop ds
ASSUME ds:USB_DSEG
UBPKD_NextScanCode:
add bx, 3
loop UBPKD_CheckScanCode
UBPKD_Exit:
popa
ret
USBBB_ProcessKeyboardData ENDP
USBKeyboardScanCodeTable LABEL BYTE
DB MKF_USB_CTRL_HOME_STATUS, MKF_USB_CTRL_HOME_KEY, \
destroy_cmos_bit + recovery_request_bit
DB MKF_USB_CTRL_PGDN_STATUS, MKF_USB_CTRL_PGDN_KEY, \
recovery_request_bit
DB MKF_USB_CTRL_PGUP_STATUS, MKF_USB_CTRL_PGUP_KEY, \
flash_program_bit + destroy_nvram_bit + \
destroy_cmos_bit + recovery_request_bit
;; DB MKF_USB_SCAN_1,MKF_USB_SCAN_2
;; DB MKF_USB_SCAN_3,MKF_USB_SCAN_4
;; DB MKF_USB_SCAN_5,MKF_USB_SCAN_6
Comment ~
KEY_COMBINATION_STRUC {ctrl_key_bit + home_key_bit, \
destroy_cmos_bit + recovery_request_bit}
KEY_COMBINATION_STRUC {ctrl_key_bit + pgdn_key_bit, \
recovery_request_bit}
KEY_COMBINATION_STRUC {ctrl_key_bit + pgup_key_bit, \
flash_program_bit + destroy_nvram_bit + \
destroy_cmos_bit + recovery_request_bit}
EndComment ~
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure: USBBB_CaptureHCInterrupt
;
; Description: This routine makes the HC's HW invocation (SMI or IRQ) to
; point to the common routine in the wrapper.
;
; Input: None
;
; Output: None
;
; Modified: Nothing
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBBB_CaptureHCInterrupt PROC NEAR PUBLIC
push eax
push bx
; Get the IRQ number
mov al, MKF_USB_BB_IRQ
add al, 8 ;IRQ 0/1/../7 -> INT 8/9/../F
cmp al, 10h
jb InitVector ;Br if IRQ 0..7
add al, 70h - 10h ;Add offset of second 8259's vectors
InitVector:
movzx bx, al ;BX = HC's interrupt vector
shl bx, 2 ;BX = addr of interrupt vector to hook
mov ax, cs ;AX = CS
shl eax, 16 ;Put CS in upper half of EAX
mov ax, OFFSET cs:USBInterruptHandler
;EAX = CS:Offset of USB's ISR
push ds
push 0 ;Set DS = 0
pop ds
xchg DWORD PTR [bx], eax ;Hook interrupt
pop ds
; Save the old interrupt value in the HCStruc
mov dNextISR, eax
; Unmask the host controller's IRQ level in the 8259
push cx
mov cl, MKF_USB_BB_IRQ
; CL = IRQ used by the HC (0..15)
mov bx, 1
shl bx, cl ;BX = bit map with one bit set
not bx ;BX = bit map with one bit clear
pop cx
;; in al, 21h ;AL = First 8259's mask reg
;; and al, bl ;Adjust mask
;; out 21h, al ;Write mask back
;;
;; in al, 0A1h ;AL = Second 8259's mask reg
;; and al, bh ;Adjust mask
;; out 0A1h, al ;Write mask back
push dx
mov dx, (1 SHL MKF_USB_BB_IRQ)
call USBBBUnmaskIRQ_FAR
pop dx
UWCHI_Exit:
pop bx
pop eax
ret
USBBB_CaptureHCInterrupt ENDP
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure: USBInterruptHandler
;
; Description: This is the common interrupt service routine which handles
; all the USB HC interrupts. This routine will call individual
; host controller interrupt handlers depending upon the
; interrupt status.
;
; Input: Nothing
;
; Output: Nothing
;
; Modified: Nothing
;
; Referrals: HCStruc
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBInterruptHandler PROC NEAR PUBLIC
; Following two push instructions are used for ISR chaining
push 0 ; Used for storing IP (SP + 8)
push 0 ; Used for storing CS (SP + 6)
cli
push ax ; Using original stack (SP + 4)
push ds ; Using original stack (SP + 2)
push es ; Using original stack (SP + 0)
; Get data segment
mov ax, USB_DSEG
mov ds, ax
mov es, ax
; DS - Data segment
; Check for re-entrancy
cmp USBReentrantFlag, TRUE
je UWIH_ExitISR ; Re-entering. Exit !
; Set re-entrancy flag
mov USBReentrantFlag, TRUE
;;; Save original stack
;; mov USBOldSP, sp
;; mov USBOldSS, ss
;;
;;; Set new stack
;; mov ax, ds
;; mov ss, ax
;; mov sp, OFFSET USBStackLoc
pushad
mov bx, CurrentHC.pHCDPointer
call (BBHCDHEADER PTR CS:[bx]).pHCDProcessInterrupt
UWIH_IssueEOI:
mov cl, MKF_USB_BB_IRQ
; Send EOI to the interrupt controller
mov al, 20h ;AL = EOI command
cmp cl, 8
jb UWIH_EoiPri ;Br if using IRQ 0..7 (2nd 8259 needs no EOI)
out 0A0h, al
jcxz $+2
jcxz $+2
UWIH_EoiPri:
out 20h, al
jcxz $+2
jcxz $+2
UWIH_LeaveISR:
popad
;;; Restore stack
;; mov ss, USBOldSS
;; mov sp, USBOldSP
mov USBReentrantFlag, FALSE
UWIH_ExitISR:
pop es ; Restore from original stack
pop ds ; Restore from original stack
pop ax ; Restore from original stack
add sp, 4
iret
USBInterruptHandler ENDP
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
;
; Procedure: USBBBUnmaskIRQ_FAR
;
; Description: This routine will unmask USB interrupt and set it to
; level trigger mode
;
; Input: DX - Interrupt bit mask
;
; Output: None
;
; Modified: AL
;
; Notes: CPU is in big real mode
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBBBUnmaskIRQ_FAR PROC FAR PUBLIC
push bx
push dx
in al, I_S_M_PORT ; Read interrupt slave mask port
mov bh, al
IO_DELAY
in al, I_M_M_PORT ; Read interrupt master mask port
mov bl, al ; BX contains Slave/Master mask in BH/BL
IO_DELAY
mov ax, dx
or ah, ah ; Any IRQ level > 7
jz @F
or al, BIT2 ; Unmask IRQ 2 to control upper IRQs
@@: not ax
and ax, bx
out I_M_M_PORT, al ; (#1) mask value
mov al, ah
out I_S_M_PORT, al ; (#2) mask value
; Set the requested IRQs as level triggered
mov ax, dx
mov dx, 4D0h
out dx, al
IO_DELAY
mov al, ah
inc dx
out dx, al
pop dx
pop bx
ret
USBBBUnmaskIRQ_FAR ENDP
ENDIF ;; IF MKF_USB_BB_DEV_KBD
PUBLIC _USBBB_ASM_END
_USBBB_ASM_END LABEL BYTE
;----------------------------------------------------------------------------
; END OF ROUTINES
;----------------------------------------------------------------------------
USB_CSEG ENDS
;----------------------------------------------------------------------------
; D A T A S E G M E N T
;----------------------------------------------------------------------------
USB_DATA SEGMENT PARA PUBLIC 'DATA'
USB_HC_DATA_AREA DB (4 * 1024) DUP (?)
USB_DATA ENDS
;----------------------------------------------------------------------------
; D A T A S E G M E N T
;----------------------------------------------------------------------------
USB_DSEG SEGMENT PARA PUBLIC 'DATA'
;;ALIGN 2
;; DW 512 DUP (?) ; Stack
;;USBStackLoc LABEL WORD
PUBLIC ControlDataBuffer
ControlDataBuffer BYTE MAX_CONTROL_DATA_SIZE DUP (?)
;----------------------------------------------------------------------------
; Current host controller related information
PUBLIC pHCInfoStrucPtr
pHCInfoStrucPtr WORD ?
PUBLIC CurrentHC
CurrentHC HCStruc <?>
bCurrentHCPortNumber BYTE ?
; Holds the number of the port that we are currently processing
PUBLIC dGlobalDataArea
dGlobalDataArea DWORD ?
; Device specific information
PUBLIC CurrentDevice
CurrentDevice DeviceInfo <?>
HubDeviceTable DeviceInfo MKF_HUB_DEVICE_LIMIT DUP (<?>)
bCurrentHubDeviceEntry BYTE ?
; Holds the index into HubDeviceTable. 0FFh indicating no hubs present
pCurrentHub WORD ?
; Holds the offset of the current hub device info entry
bCurrentDeviceAddress BYTE ?
PUBLIC dTempHubPortStatus
dTempHubPortStatus DWORD ?
dNextISR DWORD ?
USBReentrantFlag BYTE ?
;----------------------------------------------------------------------------
USB_DSEG ENDS
END
;***************************************************************************;
;***************************************************************************;
;** **;
;** (C)Copyright 1985-2002, American Megatrends, Inc. **;
;** **;
;** All Rights Reserved. **;
;** **;
;** 6145-F Northbelt Pkwy, Norcross, GA 30071 **;
;** **;
;** Phone (770)-246-8600 **;
;** **;
;***************************************************************************;
;***************************************************************************;
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -