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

📄 ezusb.bas

📁 Cypress ez-usb an2131的.hex固件程序文件下载程序
💻 BAS
字号:
Attribute VB_Name = "EZUSB"

' EZ-USB DownloadHex Example
' copyright (c) 2001 Cypress Semiconductor

Option Explicit

' = = = = W I N A P I  = = = =

Public Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Public Declare Function DeviceIoControl Lib "kernel32" (ByVal hDevice As Long, ByVal dwIoControlCode As Long, lpInBuffer As Any, ByVal nInBufferSize As Long, lpOutBuffer As Any, ByVal nOutBufferSize As Long, lpBytesReturned As Long, ByVal lpOverlapped As Long) As Long
Public Declare Function RtlMoveMemory Lib "kernel32" (dest As Any, src As Any, ByVal Count As Long) As Long

' = = = = C O N S T A N T S = = = =

Public Const GENERIC_WRITE = &H40000000
Public Const FILE_SHARE_WRITE = &H2
Public Const OPEN_EXISTING = 3

Public Const METHOD_BUFFERED = 0
Public Const METHOD_IN_DIRECT = 1
Public Const METHOD_OUT_DIRECT = 2

Public Const MAX_PIPES = 16
Public Const MAX_USB_DEV_NUMBER = 32

Enum ErrorEnum
    eBadParam = -1
    eBadDriver = -2
    eBadPipe = -3
End Enum

Enum Op_8051Enum
    eOP_8051_HOLD = 0
    eOP_8051_RUN = 1
End Enum

' = = = = I O C T L  D E F I N I O N S = = = =

' Set the base of the IOCTL control codes
Private Const Ezusb_IOCTL_INDEX = &H800

' (DeviceType) << 16) | ((Access) << 14) | ((Function) << 2) | (Method)
' note: DeviceType for each control code is FILE_DEVICE_UNKNOWN
'       FILE_DEVICE_UNKNOWN * 2^16 = &H220000
'       'Access' = FILE_ANY_ACCESS = 0

Public Const IOCTL_Ezusb_GET_PIPE_INFO = _
    &H220000 + METHOD_BUFFERED + (Ezusb_IOCTL_INDEX + 0) * 4

Public Const IOCTL_Ezusb_GET_DEVICE_DESCRIPTOR = _
    &H220000 + METHOD_BUFFERED + (Ezusb_IOCTL_INDEX + 1) * 4

Public Const IOCTL_Ezusb_GET_CONFIGURATION_DESCRIPTOR = _
    &H220000 + METHOD_BUFFERED + (Ezusb_IOCTL_INDEX + 2) * 4

Public Const IOCTL_EZUSB_BULK_READ = _
    &H220000 + METHOD_OUT_DIRECT + (Ezusb_IOCTL_INDEX + 19) * 4

Public Const IOCTL_EZUSB_BULK_WRITE = _
    &H220000 + METHOD_IN_DIRECT + (Ezusb_IOCTL_INDEX + 20) * 4
    
Public Const IOCTL_EZUSB_ANCHOR_DOWNLOAD = _
    &H220000 + METHOD_IN_DIRECT + (Ezusb_IOCTL_INDEX + 27) * 4

Public Const IOCTL_EZUSB_VENDOR_REQUEST = _
    &H220000 + METHOD_BUFFERED + (Ezusb_IOCTL_INDEX + 5) * 4
    
Public Const IOCTL_EZUSB_VENDOR_OR_CLASS_REQUEST = _
    &H220000 + METHOD_IN_DIRECT + (Ezusb_IOCTL_INDEX + 22) * 4


' = = = = U S B   R e q ' d  D a t a  T y p e s = = = =

Public Type BulkTransferControlType
    lPipeNum As Long
End Type

Public Enum USBDPipeEnum
    eUsbdPipeTypeControl = 0
    eUsbdPipeTypeIsochronous
    eUsbdPipeTypeBulk
    eUsbdPipeTypeInterrupt
End Enum

Public Type USBDPipeInformationType
    '
    ' OUTPUT
    ' These fields are filled in by USBD
    '
    iMaximumPacketSize As Integer 'Maximum packet size for this pipe
    bEndpointAddress As Byte      ' 8 bit USB endpoint address (includes direction)
                                  ' taken from endpoint descriptor
    bInterval As Byte             ' Polling interval in ms if interrupt pipe
    
    PipeType As USBDPipeEnum     ' PipeType identifies type of transfer valid for this pipe
    lPipeHandle As Long
    
    '
    ' INPUT
    ' These fields are filled in by the client driver
    '
    lMaximumTransferSize As Long  ' Maximum size for a single request
                                 ' in bytes.
    lPipeFlags As Long
End Type

Public Type USBDInterfaceInformationType
    iLength As Integer   ' Length of this structure, including
                         ' all pipe information structures that
                         ' follow.
    '
    ' INPUT
    '
    ' Interface number and Alternate setting this
    ' structure is associated with
    '
    bInterfaceNumber As Byte
    bAlternateSetting As Byte
    
    '
    ' OUTPUT
    ' These fields are filled in by USBD
    '
    bClass As Byte
    bSubClass As Byte
    bProtocol As Byte
    bReserved As Byte
    
    lInterfaceHandle As Long
    lNumberOfPipes As Long

    Pipes(MAX_PIPES) As USBDPipeInformationType
End Type

Type AnchorDownloadControlType
    offset As Integer
End Type

Type VendorRequestINType
    bRequest As Byte
    wValue As Integer
    wIndex As Integer
    wLength As Integer
    direction As Byte
    bData As Byte
End Type

Type VendorOrClassRequestControlType
   ' transfer direction (0=host to device, 1=device to host)
   direction As Byte

   ' request type (1=class, 2=vendor)
   requestType As Byte

   ' recipient (0=device,1=interface,2=endpoint,3=other)
   recepient As Byte
   '
   ' see the USB Specification for an explanation of the
   ' following paramaters.
   '
   requestTypeReservedBits As Byte
   request As Byte
   value As Integer
   index As Integer
End Type

Public Type USB_DD ' USB device descriptor
    Descriptor_Length As Byte
    Descriptor_Type As Byte
    Spec_Release As Integer
    Device_Class As Byte
    Device_SubClass As Byte
    Device_Protocol As Byte
    Max_Packet_Size As Byte
    Vendor_ID As Integer
    Product_ID As Integer
    Device_Release As Integer
    Manufacturer As Byte
    Product As Byte
    Serial_Number As Byte
    Number_Configurations As Byte
    fill(128) As Byte
End Type

Public Function GetDeviceDescriptor(driver As String, usbDD As USB_DD) As Integer
Dim result As Long
Dim hDriverHandle As Long
Dim lBytesReturned As Long

hDriverHandle = OpenDriver(driver)

If hDriverHandle > 0 Then
    result = DeviceIoControl(hDriverHandle, _
        IOCTL_Ezusb_GET_DEVICE_DESCRIPTOR, usbDD, Len(usbDD), _
        usbDD, Len(usbDD), lBytesReturned, 0)
        
    CloseHandle hDriverHandle
Else
    result = 0
End If

GetDeviceDescriptor = result

End Function




Function GetPipeInfo(strDriver As String, pi As USBDInterfaceInformationType) As Long
'   retrieves information about available pipes
'
'   IN  strDriver   symbolic link name assigned to device driver, e.g. "Ezusb-0"
'   OUT pi          holds information about pipes after successful return
'
'   returns:        1 = successful call
'                   0 = unsuccessful call

Dim result As Long
Dim hDriverHandle As Long
Dim lBytesReturned As Long

hDriverHandle = OpenDriver(strDriver)

GetPipeInfo = 0

If hDriverHandle > 0 Then

    result = DeviceIoControl(hDriverHandle, IOCTL_Ezusb_GET_PIPE_INFO, pi, Len(pi), pi, Len(pi), lBytesReturned, 0)
    CloseHandle (hDriverHandle)
End If

GetPipeInfo = result

End Function


Function OpenDriver(sDriverName As String) As Long
' get handle to EZ-USB driver
'
'   IN  sDriverName     symbolic link name assigned during enumeration
'
'   returns:            driver handle
'
'   called by:          BulkXFer
'                       GetPipeInfo


OpenDriver = CreateFile("\\.\" & sDriverName, GENERIC_WRITE, FILE_SHARE_WRITE, ByVal 0, OPEN_EXISTING, 0&, 0)

End Function

Sub ErrMsg(err As ErrorEnum)
' display error messages to user
'
'   IN  err         error code returned from BulkXfer
'
'   called By:          BulkXfer
    
Select Case err
        
    Case eBadDriver
        MsgBox "Selected EZ-USB Device Driver was not found." & vbCrLf & "Perhaps no device is connected.", vbOKOnly + vbCritical, "DownloadHex Error"
    Case Else
        MsgBox "Unknown Error.", vbOKOnly + vbCritical, "DownloadHex Error"
End Select

End Sub

Public Function Reset_Or_Hold_8051(hDriver As Long, op_8051 As Op_8051Enum) As Long
Dim hDriverHandle As Long
Dim result As Long
Dim nBytes As Long
Dim vendReq As VendorRequestINType
Dim temp As Boolean

    With vendReq
        .bRequest = &HA0
        .wValue = &H7F92
        .wIndex = 0
        .wLength = 1
        .direction = 0
        .bData = (op_8051 = eOP_8051_HOLD)
    End With

    temp = vendReq.bData
    
    result = DeviceIoControl(hDriver, _
                        IOCTL_EZUSB_VENDOR_REQUEST, _
                        vendReq, _
                        LenB(vendReq), _
                        0, _
                        0, _
                        nBytes, _
                        0)

End Function

⌨️ 快捷键说明

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