⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 usb.asm

📁 dos下的USB源码(包括UHCI
💻 ASM
📖 第 1 页 / 共 5 页
字号:
; Set return code as error
	mov	dx, USB_ERROR

; Start from first HCStruc
	mov	si, 0FFFFh

; Get and set the data segment address
	xor	ax, ax
	call	USBGetDataSegment
	jz	UAS_Exit

; DS - Data segment value

; Assume successful completion
	mov	dx, USB_SUCCESS

UAS_ProcessNextHCStruc:
; Get next HCStruc
	call	USBGetNextHCStruc	; SI - HCStruc
	jz	UAS_Exit

; SI - New HCStruc

	push	bx		; Save the offset
; Invoke the stop routine in the HCDDriver
; Offset in BX already
	add	bx, (HCStruc PTR [si]).pHCDPointer
	call	NEAR PTR CS:[BX]	; SI - HCStruc
	pop	bx		; Restore the offset
	jmp	SHORT UAS_ProcessNextHCStruc

UAS_Exit:
	mov	ax, dx		; Return value
	ret
USBCallAllHC		ENDP

;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure:	USBVerifyUSBClassCode
;
; Description:	This routine checks whether the PCI device pointed by bus,
;		device and function number is really USB host controller.
;
; Input: 	AX	HC PCI address
;
; Output: 	AX	USB host controller type. Carry flag is reset
;		AX	0 if the device is not a valid PCI device or if it is
;			  not a USB host controller. Carry flag is set
;
; Modified:	AX
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>

USBVerifyUSBClassCode	PROC NEAR SYSCALL PUBLIC

	push	ebx
	push	dx

	mov	dx, ax
; Valid bus, device and function number
; Get the PCI device type
; DX	Bus, Device and Function Number
	mov	ah, 8			; Read register 8 (DWORD)
	call	read_pci_dword_FAR	; Value in EBX
	mov	eax, ebx

	inc	eax
	jz	UWVUCC_Error

	shr	eax, 8			; Get regs. 8, 9 & A only
	mov	bl, al			; HC type
	shr	eax, 8			;

	cmp	eax, USB_HC_CLASS_CODE	; Check for USB HC device
	jne	UWVUCC_Error		; If not, return error

; Valid USB HC device found. Get proper type
	add	bl, USB_UHCI		; Get USB HC type
	movzx	ax, bl
	clc
	jmp	SHORT UWVUCC_Exit

UWVUCC_Error:
;;	mov	ax, ERRUSB_HC_NOT_FOUND
;;	call	USBLogError
	xor	ax, ax

UWVUCC_Exit:

	pop	dx
	pop	ebx
	ret
USBVerifyUSBClassCode	ENDP

;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure:	USBGetHCAddress
;
; Description:	This routine returns the PCI bus, device and function number
;		of the USB host controller.
;
; Input: 	DL	0-based USB host controller number
;			(0..MKF_USB_MAX_HC-1)
; Output: 	AH	PCI Bus number
;		AL	Device / Function number
;				Bits 7-3: PCI device number
;				Bits 2-0: Function number within the device
;		AX	if the requested HC is not found
;
; Modified:	AX
;
; Notes:	This function only returns PCI bus, device and function
;		number from HC PCI lookup tables. The order of the HC types
;		is the following: UHCI->OHCI->EHCI
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>

USBGetHCAddress		PROC NEAR SYSCALL PUBLIC USES DX SI
	xor	ax, ax				; Initialize AX with "Not Found"
	mov	si, OFFSET USBHCInfoTableStart

UPGHA_NextEntry:
	cmp	(HCPCIInfo PTR [si]).bAvailable, TRUE
	je	UPGHA_AdjustPtr			; Skip available entries
	sub	dl, 1			; DEC does not affect CF
	jc	UPGHA_Exit			; Br if found

UPGHA_AdjustPtr:
	add	si, SIZE HCPCIInfo
	cmp	si, OFFSET USBHCInfoTableEnd
	clc
	jne	UPGHA_NextEntry			; Br if table ends

; At this point CF if entry is found, NC otherwise
UPGHA_Exit:
	jnc	UPGHA_Ret			; AX = 0
	mov	ax, (HCPCIInfo PTR [si]).wBusDevFun
UPGHA_Ret:
	ret
USBGetHCAddress		ENDP

;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure:	USBHCInit
;
; Description:	This routine searches for proper host controller driver
;		for the HC and initializes it
;
; Input: 	EDI	32bit absolute data area address
;		EBX	Size of the data area (in bytes)
;		AL	Host controller type
;		CX	HC PCI address
;		DL	HC number (0-based)
;
; Output: 	EAX	Size of data area used by the HC
;
; Modified:	EAX
;
; Referrals:	USBFindHCDriver, HCStruc, USBGetHCStruc
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>

USBHCInit	PROC NEAR SYSCALL PUBLIC
	LOCAL	wErrorCode

	push	bx
	push	ecx
	push	dx
	push	si

	mov	dh, al		; Save HCType
; AL - Host controller type to look for
; Set the zero flag indicating HC driver is not found
	cmp	sp, sp
	call	farUSBFindHCDriver		; eLink
	jnz	UHI_DriverFound

; Valid driver not found. Exit with error.
UHI_DriverErrorExit:

	mov	wErrorCode, USB_ERR_NO_DRIVER

UHI_ErrorExit:

; Log error
	mov	ax, wErrorCode
	call	USBLogError
	stc
	jmp	short UHI_Exit

UHI_DriverFound:

; AX	HC driver address

; Find a free HCStruc structure from the HCDriver table
	call	USBGetHCStruc
	mov	wErrorCode, USB_ERR_NO_HCSTRUC
	jz	UHI_ErrorExit

; SI	HCStruc
; AX	HC driver address
; Fill the HCStruc structure
	mov	(HCStruc PTR [si]).pHCDPointer, ax
	mov	(HCStruc PTR [si]).bHCType, dh
	mov	(HCStruc PTR [si]).wBusDevFuncNum, cx
	mov	(HCStruc PTR [si]).bNumPorts, 0

	mov	ecx, ebx	; Data area size
	mov	bx, ax		; HC Driver Pointer

	inc	dl					; HC number (1 based)
	mov	(HCStruc PTR [si]).bHCNumber, dl

; Initialize the HC param pointers.
; BX	Pointer to HCDriver
; SI	HCStruc pointer
; EDI	Data area address
; ECX	Data area size
	call	(HCDHEADER PTR cs:[bx]).pHCDStart
; EAX	Data area size used

UHI_Exit:
	pop	si
	pop	dx
	pop	ecx
	pop	bx
	ret
USBHCInit	ENDP

;<AMI_PHDR_START>
;----------------------------------------------------------------------------
; Procedure:	USBStartHC
;
; Description:	This API routine configures the USB host controllers and
;		enumerate the devices
;
; Input: 	AX	Indicates which data area to use
;
; Output: 	AX 	Current data area pointer on success
;			0xFFFF on error
;
; Modified:	EAX
;
;----------------------------------------------------------------------------
;<AMI_PHDR_END>

USBStartHC	PROC NEAR SYSCALL PUBLIC

	LOCAL	wRetValue:WORD

	pushad
	push	ds
	push	es

; AX - Data segment value to get
	call	USBGetDataSegment
; DS - Data segment

	mov	ax, ds
	mov	wRetValue, ax

; Check if size of data area is reasonable
	mov	ax, MKF_USB_DATA_AREA_SIZE
	cmp	ax, (USB_GLOBAL_DATA_SIZE SHR 10)
IF	MKF_ENABLE_EXT_MEMORY_DATA_AREA
	jb	USH_ErrorExit		; Not enough memory. Exit.
ELSE
	jbe	USH_ErrorExit		; Not enough memory. Exit.
ENDIF

; Initialize the memory for global data
	push	di

	push	ds
	pop	es
	xor	di, di			; Start at offset 0
	mov	cx, (USB_GLOBAL_DATA_SIZE / 4)
	xor	eax, eax

	rep	stosd			; Clear entire USB data area

	pop	di

; Set the signature
	mov	USBDataAreaSignature, '$UDA'

; Set the version number
	mov	USBVersion, ((USB_BIOS_MAJOR_VERSION SHL 8) + USB_BIOS_MINOR_VERSION)

; Signal the USB is not used by OS
	mov	USBAcquiredByOS, FALSE

; Save extended data area pointer in the data area
	mov	dUSBExtMemoryStart, esi

IF	MKF_USB_DEV_MASS
; Set the USB data area address in the INT13h runtime code segment
	push	es
	mov	ax, I13R_CSEG
	mov	es, ax
	push	ds
	pop	WORD PTR ES:wUSBGlobalDataSegment
	pop	es
ENDIF

; Update debug table pointers
	mov	ax, OFFSET HCTable
	mov	USBHCTablePtr, ax

	mov	ax, OFFSET IRQInfoTable
	mov	USBIRQTablePtr, ax

	mov	ax, OFFSET DeviceInfoTable
	mov	USBDeviceInfoTablePtr, ax

IF	MKF_USB_DEV_MASS
	mov	ax, OFFSET MassDeviceInfoTable
	mov	USBMassInfoTablePtr, ax
ENDIF

	mov	bHandOverInProgress, FALSE

; Read the setup options and save it locally
	xor	eax, eax
	mov	dUSBInitFlag, eax

	mov	bx, OFFSET USBCmosQuestionInitTable
USH_ReadNextEntry:
	cmp	bx, OFFSET USBCmosQuestionInitTableEnd
	jae	USH_CMOSReadDone

	mov	ax, (USB_CMOS_INIT_STRUC PTR CS:[bx]).wQuestionNumber
	call	check_cmos_data_far
	jz	USH_PrepareForLoop

	mov	eax, (USB_CMOS_INIT_STRUC PTR CS:[bx]).dSetMask
	or	dUSBInitFlag, eax

USH_PrepareForLoop:
	add	bx, SIZE USB_CMOS_INIT_STRUC
	jmp	SHORT USH_ReadNextEntry

USH_CMOSReadDone:

; Set the current mode
	mov	bUSBMode, MKF_USB_MODE

; Initialize the memory pool
	call	USBMem_Init

; Scan for host controllers
	call	USBMiscFindHC

; Fill the device driver Entry Point
	call	USBMiscFillDeviceDriverTable


; Set the time out value for Control, bulk & interrupt transfer	
	mov	wTimeOutValue, 5	; Approximately 5 seconds

; Invoke device drivers initialize routine
	mov	si, OFFSET DeviceDriverTable
USH_CheckNextDriver:
; Check for driver validity
	mov	bx, WORD PTR cs:[si]
	or	bx, bx
	jz	USH_DriverInitDone

; Check whether device init routine is implemented
	cmp	(USB_DEV_HDR PTR cs:[bx]).pDevInit, 0
	je	USH_TryNextDriver

	call	(USB_DEV_HDR PTR cs:[bx]).pDevInit
USH_TryNextDriver:
	add	si, 2
	jmp	SHORT USH_CheckNextDriver

USH_DriverInitDone:

; Initialize the data structures

; Allocate a block of memory to be used as a temporary
; buffer for  USB mass transfer
	mov	al, (MAX_CONTROL_DATA_SIZE / USB_MEM_BLK_SIZE)
	call	USBMem_Alloc
	jz	USH_ErrorExit

	mov	pUSBMassConsumeBuffer, ax

; Allocate a block of memory for the temporary buffer
	mov	al, (MAX_TEMP_BUFFER_SIZE / USB_MEM_BLK_SIZE)
	call	USBMem_Alloc
	jz	USH_ErrorExit

	mov	pUSBTempBuffer, ax

; Setup entry 0 in the DeviceInfoTable as used.
	mov	bx, OFFSET DeviceInfoTable	; BX = ptr to entry for device address 0
	mov	(DeviceInfo PTR [bx]).bFlag, DEV_INFO_VALID_STRUC

; Initialize remaining entries in device table to unused.
	add	bx, SIZE DeviceInfo		; BX = ptr to entry for device address 1
UBS_InitDevTableLoop:
	mov	(DeviceInfo PTR [bx]).bFlag, 0
	add	bx, SIZE DeviceInfo		; BX = ptr to next entry
	cmp	bx, OFFSET DeviceInfoTableEnd
	jb	UBS_InitDevTableLoop

; Find and configure each host controller iteratively.

; Set EDI to 32bit absolute address of USB BIOS data area
	push	ds
	pop	ax
	movzx	eax, ax
	shl	eax, 4
	mov	HcdGlobalDataArea, eax
; Set EDI to data area start address for the host controller
IF	MKF_ENABLE_EXT_MEMORY_DATA_AREA
	mov	edi, dUSBExtMemoryStart
	mov	ebx, (USB_HC_EXT_MEM_SIZE SHL 10)
ELSE
	sub	eax, TOTAL_HC_DATA_AREA_SIZE
	mov	edi, eax		; 

; Get the data area size
	mov	ebx, MKF_USB_DATA_AREA_SIZE
	shl	ebx, 10			; Size in bytes
; EBX	Size of the global data area
	sub	ebx, USB_GLOBAL_DATA_SIZE
					; Reduce global data area size
ENDIF

IF	MKF_USB_MODE GE 2
; Get the current time tick counter from BIOS data area
	push	ds
	push	40h
	pop	ds
	mov	eax, DWORD PTR DS:[6Ch]
	pop	ds
; Initialize the time counter
	mov	dTimeLastInSMI, eax
ENDIF

; Initialize the variables for the iteration
	mov	cx, MKF_USB_MAX_HC	; Iteration count
	mov	dl, 0FFh


USH_LookForNextHC:
	inc	dl
	push	ecx		; Save ECX

; DL - Zero based host controller number
	call	USBGetHCAddress
	or	ax, ax
	jz	USH_NextIteration

	mov	cx, ax

; Check for valid bus, device and function number and also get the
; USB host controller class code
; AX - PCI address
	call	USBVerifyUSBClassCode
	or	al, al
	jz	USH_NextIteration

; Give control to proper USB HC module
; EDI - Data area
; EBX - Data area size
; AL  - HC type
; CX  - PCI address
; DL  - Host controller number
	call	USBHCInit
								
; EAX - Data area used by the HC
; Adjust the data area address and data area size
	add	edi, eax
	sub	ebx, eax

USH_NextIteration:
	pop	ecx		; Restore ECX
	loop	USH_LookForNextHC

; Invoke all HC's enumerate ports routine
	mov	bx, HCDHeader.pHCDEnumeratePorts
	call	USBCallAllHC

; Successful completion
	mov	UsbBiosActive, 1

	jmp	SHORT USH_Exit

USH_ErrorExit:
; Log error
	mov	ax, USB_ERR_STARTHC_NO_MEMORY
	call	USBLogError

	mov	wRetValue, 0FFFFh

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -