📄 usb.asm
字号:
USH_Exit:
pop es
pop ds
popad
mov ax, wRetValue
ret
USBStartHC ENDP
Comment ~
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure: USBMoveDataArea
;
; Description: This API routine moves the global & host controller data
; area to a new address
;
; Input: wDataAreaFlag Indicates which data area to use
;
; Output: AX Current data area pointer on success
; 0xFFFF on error
;
; Modified: EAX
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBMoveDataArea PROC NEAR C PUBLIC USES BX SI DS ES,
wDataAreaFlag:WORD
LOCAL dDataArea:DWORD, wRetValue:WORD, wOrgDataArea:WORD,
wDataAreaSz:WORD
; Set error return value
xor ax, ax
dec ax ; 0FFFFh
mov wRetValue, ax
; Get and set the data segment address
inc ax ; 0
call USBGetDataSegment
stc
je UMDA_Exit
; DS - Data segment
; Stop all the USB host controllers
mov bx, HCDHEADER.pHCDDisableInterrupts
call USBCallAllHC
; Get the data area address to use
mov bx, ds ; Save DS
mov ax, wDataAreaFlag
call USBGetDataSegment
stc
je UMDA_Exit
; DS - Data segment
mov ax, ds
mov ds, bx
; Set ES to the new data area
sub ax, USB_HC_DATA_AREA_SIZE_PARA
mov es, ax
; dDataArea - 32bit absolute address of USB BIOS data area
movzx eax, ax
shl eax, 4
mov dDataArea, eax
; Get the data area size (in KBs)
mov eax, MKF_USB_DATA_AREA_SIZE
shl eax, 10 ; Size in bytes
; Set the counter for move data
mov ecx, eax
shr ecx, 2 ; Size in DWORD
; Save the size of the data for future use
mov wDataAreaSz, cx
; Find the start of the data area
mov ax, ds
sub ax, USB_HC_DATA_AREA_SIZE_PARA
mov ds, ax
; Save the original data area address for future use
mov wOrgDataArea, ax
; Move the data area from the current location to the new location
xor si, si
xor di, di
pushf
cld
rep movsd
popf
; Change the data segment to the new global data area
mov ax, es
add ax, USB_HC_DATA_AREA_SIZE_PARA
mov ds, ax
; Update the segment values for the global pointers
; Save original global data area address
mov eax, HcdGlobalDataArea
mov dOrgGlobalDataArea, eax
; Store the data area absolute address
mov ax, ds
movzx eax, ax
shl eax, 4
mov HcdGlobalDataArea, eax
; Start from first HCStruc
mov si, 0FFFFh
UMDA_ProcessNextHCStruc:
; Get next HCStruc
call USBGetNextHCStruc ; SI - HCStruc
clc
je UMDA_StartHC
; SI - New HCStruc
; Invoke the move data area routine in the HC driver
mov bx, (HCStruc PTR [si]).pHCDPointer
INVOKE (HCDHEADER PTR cs:[bx]).pHCDMoveDataArea, si, dDataArea
jmp SHORT UMDA_ProcessNextHCStruc
UMDA_StartHC:
; Clear old data area
mov ax, wOrgDataArea
mov es, ax
xor di, di
mov cx, wDataAreaSz
xor eax, eax
pushf
cld
rep stosd
popf
; Restart all the USB host controllers
mov bx, HCDHEADER.pHCDEnableInterrupts
call USBCallAllHC
UMDA_Exit:
mov ax, wRetValue
ret
USBMoveDataArea ENDP
EndComment ~
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure: USBCaptureHCInterrupt
;
; Description: This routine makes the HC's HW invocation (SMI or IRQ) to
; point to the common routine in the wrapper.
;
; Input: SI HCStruc pointer of the HC
;
; Output: Nothing
;
; Modified: Nothing
;
; Referrals: HCStruc
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>
USBCaptureHCInterrupt PROC NEAR PUBLIC
push ax
push bx
push dx
push si
push di
; Capture interrupt only if the current mode is IRQ or _BBLK_is defined
IF MKF_USB_MODE NE 2
; Equivalent to IFDEF _BBLK_ because MKF_USB_MODE always assigned
; to 1 for Boot Block
; Find the interrupt that has been assigned to the host controller.
mov ah, PCI_REG_INT_LINE
mov dx, (HCStruc PTR [si]).wBusDevFuncNum
call read_pci_FAR
mov dl, al
; Hook the interrupt that has been assigned to the host controller.
; Check whether this IRQ is already captured
mov dh, MKF_USB_MAX_HC
xor bx, bx
mov di, OFFSET IRQInfoTable
UWCHI_CheckNext:
cmp (IRQInfo PTR [di]).IRQNumber, al
je UWCHI_IRQAlreadyCaptured
or bx, bx
jnz UWCHI_PrepareForLoop
cmp (IRQInfo PTR [di]).IRQNumber, 0
jne UWCHI_PrepareForLoop
; This is a free entry save it in BX
mov bx, di
UWCHI_PrepareForLoop:
add di, SIZE IRQInfo
dec dh
jnz UWCHI_CheckNext
; No entry found
mov di, bx
UWCHI_IRQAlreadyCaptured:
; DI - IRQInfo structure of captured IRQ or free IRQInfo structure
; Save the IRQInfo structure in HCStruc
; This is done here also to make sure all the HCStruc which uses this IRQ
; have the corresponding IRQInfo pointer.
mov (HCStruc PTR [si]).pIRQInfoPtr, di
; Check whether this IRQ is already captured
cmp (IRQInfo PTR [di]).IRQNumber, al
je UWCHI_Exit
; Store the IRQ number
mov (IRQInfo PTR [di]).IRQNumber, al
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
IF MKF_USB_MODE EQ 1
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
ELSE
EXTERN USBInterruptHandler:NEAR
push RUN_CSEG
push OFFSET RUN_CSEG:USBInterruptHandler
pop eax
ENDIF
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 (IRQInfo PTR [di]).NextISR, eax
; Save the IRQInfo structure in HCStruc
mov (HCStruc PTR [si]).pIRQInfoPtr, di
; Unmask the host controller's IRQ level in the 8259
push cx
mov cl, (IRQInfo PTR [di]).IRQNumber
; 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
UWCHI_Exit:
ENDIF ; IRQ mode (always IRQ)
pop di
pop si
pop dx
pop bx
pop ax
ret
USBCaptureHCInterrupt ENDP
;----------------------------------------------------------------------------
; Interrupt handlers are different for IRQ and SMI
; USBInterruptHandler is needed only for IRQ mode of POST/RUNTIME
; and for BootBlock
IF MKF_USB_MODE EQ 1
;<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
xor ax, ax
call USBGetDataSegment
je UWIH_ExitISR ; Undefined DS. Exit !
; DS - Data segment
push ds
pop es
; 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
call USBMiscFindIRQInService
or ax, ax
jz UWIH_LeaveISR
; Give control to all the HC which matches this IRQ
mov si, OFFSET HCTable
mov cx, MKF_USB_MAX_HC
xor dx, dx
UWIH_TryNextHC:
cmp (HCStruc PTR [si]).pIRQInfoPtr, 0
jz UWIH_PrepareForLoop
mov di, (HCStruc PTR [si]).pIRQInfoPtr
cmp (IRQInfo PTR [di]).IRQNumber, al
jne UWIH_PrepareForLoop
; Structure found
mov bx, (HCStruc PTR [si]).pHCDPointer
push ax
; SI - HCStruc pointer
call (HCDHEADER PTR cs:[bx]).pHCDProcessInterrupt
or ax, ax
pop ax
jz UWIH_PrepareForLoop ; Interrupt not serviced
; Interrupt serviced. Set flag to send EOI
mov dx, si ; Save the HCStruc value
; Check for more HCs using same IRQ
UWIH_PrepareForLoop:
add si, SIZE HCStruc
loop UWIH_TryNextHC
; Check whether IRQ is serviced
or dx, dx
jnz UWIH_IssueEOI
; Otherwise chain the ISR. Chaining is done by directly adjusting
; CS:IP stored during interrupt invocation
push ds
mov eax, (IRQInfo PTR [di]).NextISR
mov bx, USBOldSP
mov ds, USBOldSS
mov DWORD PTR ds:[bx+6], eax
pop ds
mov USBChainISR, TRUE
jmp short UWIH_LeaveISR
UWIH_IssueEOI:
mov cl, al
; 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
; Check whether to chain the ISR or leave the ISR
cmp USBChainISR, TRUE
jne UWIH_ClearFlag
mov USBChainISR, FALSE
mov USBReentrantFlag, FALSE
pop es ; Restore from original stack
pop ds ; Restore from original stack
pop ax ; Restore from original stack
retf
UWIH_ClearFlag:
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
ENDIF ;; MKF_USB_MODE EQ 1
IF MKF_USB_MODE GE 2 ; SMI mode and not for BootBlock
;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure: farUSBSMIHandler
;
; 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>
farUSBSMIHandler PROC FAR PUBLIC
; Interrupt handlers are different for IRQ and SMI
push ds
push es
pushad
; Get data segment
xor ax, ax
call USBGetDataSegment
je UWIH_ExitISR ; Undefined DS. Exit !
; DS - Data segment
push ds
pop es
; Reset re-init flag
mov bReInitUSB, FALSE
; Test to see if we are in POST. No need to set this flag in POST
cmp USBAcquiredByOS, TRUE
jne fUSH_ProcessTimeDone
; Get the time last we were in SMI
mov ebx, dTimeLastInSMI
; Get the current time tick counter from BIOS data area
push ds
push 40h
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -