Continue to Site

Welcome to our site!

Electro Tech is an online community (with over 170,000 members) who enjoy talking about and building electronic circuits, projects and gadgets. To participate you need to register. Registration is free. Click here to register now.

  • Welcome to our site! Electro Tech is an online community (with over 170,000 members) who enjoy talking about and building electronic circuits, projects and gadgets. To participate you need to register. Registration is free. Click here to register now.

Help Needed in Connecting PIC to PC via USB

Status
Not open for further replies.

mosh11

New Member
Currently i am doing my bachelor project.

the idea of the project is to control several devices and systems using PC, i will connect the PC to PIC using USB interface

i already found the circuit and connected it and also the pc (windows xp sp2) identified my circuit as Human Interface device(HID).

● The problem now how can i test this connection(how do i send and receive data between both terminals)?


● Which program language or platform can i use to have access to usb port in the PC?


--here is code that i downloaded to the PIC microcontroller

1-The interrupt part for keeping the connection alive by sending message every 3.3ms

2-When pic receives (P=??) it is expected to send to PC data on PORTC

When it receives (P=nT) it is expected to output n in PORTB

Code:
#include "C:\Program Files\Mikroelektronika\mikroC\Examples\EasyPic4\extra_examples\HID-library\USBdsc.c"
unsigned char Read_buffer[64];
unsigned char Write_buffer[64];
unsigned char num,x;
//
// Timer interrupt service routine
//
void interrupt()
{
HID_InterruptProc(); // Keep alive
TMR0L = 100 ; // Re-load TMR0L
INTCON.TMR0IF = 0 ;  // Reload TMR0
}


void main()
{

ADCON1 = 0xFF; // Set PORTB to digital I/O
TRISB=0; // Set PORTB to outputs
TRISD=0;
TRISC=1;
PORTD=0;
PORTB = 0; // Clear all outputs

INTCON=0;
INTCON2=0xF5;
INTCON3=0xC0;
RCON.IPEN=0;
PIE1=0;
PIE2=0;
PIR1=0;
PIR2=0;
//
// Configure TIMER 0 for 3.3ms interrupts. Set prescaler to 256
// and load TMR0L to 100 so that the time interval for timer
// interrupts at 48MHz is 256.(256-100).0.083 = 3.3ms
//
// The timer is in 8-bit mode by default
//
T0CON = 0x47; // Prescaler = 256
TMR0L = 100; // Timer count is 256-156 = 100
INTCON.TMR0IE = 1; // Enable T0IE
T0CON.TMR0ON = 1; // Turn Timer 0 ON
INTCON = 0xE0; // Enable interrupts

// Enable USB port

Hid_Enable(&Read_buffer, &Write_buffer);
Delay_ms(2000);

// Read from the USB port. Number of bytes read is in num

for(;;) // do forever
{

if(Read_buffer[0]=='P' && Read_buffer[1]=='=' && Read_buffer[2]=='?' && Read_Buffer[3]=='?' ){


while(!Hid_Write(PORTC, 1)){
                   x = Hid_Write(PORTC, 1);
                   }
}

 // Read from the USB port. Number of bytes read is in num

if(Read_buffer[0] == 'P' && Read_buffer[1] == '=' && Read_buffer[3] == 'T')
{
if(Read_buffer[2]=='1'){
PORTD=1; // opens gate
}
PORTB = Read_buffer[2];
}
}
Hid_Disable();
}
 
I HAVE ALL THIS DONE ¡ ¡ ¡

LowPinCount board and some visual C++ code edition and I can see Data from PIC to PC and PC from PIC.

The PIC is 18f14k50 and the program is Generic Simple HID Demo The project in Visual C++ 2005 and project for MPLAB, all is done here.
 
I HAVE ALL THIS DONE ¡ ¡ ¡

LowPinCount board and some visual C++ code edition and I can see Data from PIC to PC and PC from PIC.

The PIC is 18f14k50 and the program is Generic Simple HID Demo The project in Visual C++ 2005 and project for MPLAB, all is done here.

here ?? where?
 
Code for interfacing with USB devices

I usually use PIC18 simulator USB add-ons (hidterm.dll) but this is only available to licenced users. Here's some VB6 code for interfacing with a USB device that I found on the net a while ago.
Create a module and paste this into it - more to follow in successive posts due to character size limit in forum posts:

Code:
'******************************************************************************
'API constants, listed alphabetically
'******************************************************************************

'from setupapi.h
Public Const DIGCF_PRESENT = &H2
Public Const DIGCF_DEVICEINTERFACE = &H10
Public Const FILE_FLAG_OVERLAPPED = &H40000000
Public Const FILE_SHARE_READ = &H1
Public Const FILE_SHARE_WRITE = &H2
Public Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
Public Const GENERIC_READ = &H80000000
Public Const GENERIC_WRITE = &H40000000

'Typedef enum defines a set of integer constants for HidP_Report_Type
'Remember to declare these as integers (16 bits)
Public Const HidP_Input = 0
Public Const HidP_Output = 1
Public Const HidP_Feature = 2

Public Const OPEN_EXISTING = 3
Public Const WAIT_TIMEOUT = &H102&
Public Const WAIT_OBJECT_0 = 0

'******************************************************************************
'User-defined types for API calls, listed alphabetically
'******************************************************************************

Public Type GUID
    Data1 As Long
    Data2 As Integer
    Data3 As Integer
    Data4(7) As Byte
End Type

Public Type HIDD_ATTRIBUTES
    Size As Long
    VendorID As Integer
    ProductID As Integer
    VersionNumber As Integer
End Type

'Windows 98 DDK documentation is incomplete.
'Use the structure defined in hidpi.h
Public Type HIDP_CAPS
    Usage As Integer
    UsagePage As Integer
    InputReportByteLength As Integer
    OutputReportByteLength As Integer
    FeatureReportByteLength As Integer
    Reserved(16) As Integer
    NumberLinkCollectionNodes As Integer
    NumberInputButtonCaps As Integer
    NumberInputValueCaps As Integer
    NumberInputDataIndices As Integer
    NumberOutputButtonCaps As Integer
    NumberOutputValueCaps As Integer
    NumberOutputDataIndices As Integer
    NumberFeatureButtonCaps As Integer
    NumberFeatureValueCaps As Integer
    NumberFeatureDataIndices As Integer
End Type

'If IsRange is false, UsageMin is the Usage and UsageMax is unused.
'If IsStringRange is false, StringMin is the string index and StringMax is unused.
'If IsDesignatorRange is false, DesignatorMin is the designator index and DesignatorMax is unused.
Public Type HidP_Value_Caps
    UsagePage As Integer
    ReportID As Byte
    IsAlias As Long
    BitField As Integer
    LinkCollection As Integer
    LinkUsage As Integer
    LinkUsagePage As Integer
    IsRange As Long
    IsStringRange As Long
    IsDesignatorRange As Long
    IsAbsolute As Long
    HasNull As Long
    Reserved As Byte
    BitSize As Integer
    ReportCount As Integer
    Reserved2 As Integer
    Reserved3 As Integer
    Reserved4 As Integer
    Reserved5 As Integer
    Reserved6 As Integer
    LogicalMin As Long
    LogicalMax As Long
    PhysicalMin As Long
    PhysicalMax As Long
    UsageMin As Integer
    UsageMax As Integer
    StringMin As Integer
    StringMax As Integer
    DesignatorMin As Integer
    DesignatorMax As Integer
    DataIndexMin As Integer
    DataIndexMax As Integer
End Type

Public Type OVERLAPPED
    Internal As Long
    InternalHigh As Long
    Offset As Long
    OffsetHigh As Long
    hEvent As Long
End Type

Public Type SECURITY_ATTRIBUTES
    nLength As Long
    lpSecurityDescriptor As Long
    bInheritHandle As Long
End Type

Public Type SP_DEVICE_INTERFACE_DATA
   cbSize As Long
   InterfaceClassGuid As GUID
   Flags As Long
   Reserved As Long
End Type

Public Type SP_DEVICE_INTERFACE_DETAIL_DATA
    cbSize As Long
    DevicePath As Byte
End Type

Public Type SP_DEVINFO_DATA
    cbSize As Long
    ClassGuid As GUID
    DevInst As Long
    Reserved As Long
End Type

'******************************************************************************
'API functions, listed alphabetically
'******************************************************************************

Public Declare Function CancelIo _
    Lib "kernel32" _
    (ByVal hFile As Long) _
As Long

Public Declare Function CloseHandle _
    Lib "kernel32" _
    (ByVal hObject As Long) _
As Long

Public Declare Function CreateEvent _
    Lib "kernel32" _
    Alias "CreateEventA" _
    (ByRef lpSecurityAttributes As SECURITY_ATTRIBUTES, _
    ByVal bManualReset As Long, _
    ByVal bInitialState As Long, _
    ByVal lpName As String) _
As Long

Public Declare Function CreateFile _
    Lib "kernel32" _
    Alias "CreateFileA" _
    (ByVal lpFileName As String, _
    ByVal dwDesiredAccess As Long, _
    ByVal dwShareMode As Long, _
    ByRef lpSecurityAttributes As SECURITY_ATTRIBUTES, _
    ByVal dwCreationDisposition As Long, _
    ByVal dwFlagsAndAttributes As Long, _
    ByVal hTemplateFile As Long) _
As Long

Public Declare Function FormatMessage _
    Lib "kernel32" _
    Alias "FormatMessageA" _
    (ByVal dwFlags As Long, _
    ByRef lpSource As Any, _
    ByVal dwMessageId As Long, _
    ByVal dwLanguageZId As Long, _
    ByVal lpBuffer As String, _
    ByVal nSize As Long, _
    ByVal Arguments As Long) _
As Long

Public Declare Function HidD_FreePreparsedData _
    Lib "hid.dll" _
    (ByRef PreparsedData As Long) _
As Long

Public Declare Function HidD_GetAttributes _
    Lib "hid.dll" _
    (ByVal HidDeviceObject As Long, _
    ByRef Attributes As HIDD_ATTRIBUTES) _
As Long

'Declared as a function for consistency,
'but returns nothing. (Ignore the returned value.)
Public Declare Function HidD_GetHidGuid _
    Lib "hid.dll" _
    (ByRef HidGuid As GUID) _
As Long

Public Declare Function HidD_GetPreparsedData _
    Lib "hid.dll" _
    (ByVal HidDeviceObject As Long, _
    ByRef PreparsedData As Long) _
As Long

Public Declare Function HidP_GetCaps _
    Lib "hid.dll" _
    (ByVal PreparsedData As Long, _
    ByRef Capabilities As HIDP_CAPS) _
As Long

Public Declare Function HidP_GetValueCaps _
    Lib "hid.dll" _
    (ByVal ReportType As Integer, _
    ByRef ValueCaps As Byte, _
    ByRef ValueCapsLength As Integer, _
    ByVal PreparsedData As Long) _
As Long
       
Public Declare Function lstrcpy _
    Lib "kernel32" _
    Alias "lstrcpyA" _
    (ByVal dest As String, _
    ByVal source As Long) _
As String

Public Declare Function lstrlen _
    Lib "kernel32" _
    Alias "lstrlenA" _
    (ByVal source As Long) _
As Long

Public Declare Function ReadFile _
    Lib "kernel32" _
    (ByVal hFile As Long, _
    ByRef lpBuffer As Byte, _
    ByVal nNumberOfBytesToRead As Long, _
    ByRef lpNumberOfBytesRead As Long, _
    ByRef lpOverlapped As OVERLAPPED) _
As Long

Public Declare Function ResetEvent _
    Lib "kernel32" _
    (ByVal hEvent As Long) _
As Long

Public Declare Function RtlMoveMemory _
    Lib "kernel32" _
    (dest As Any, _
    src As Any, _
    ByVal Count As Long) _
As Long

Public Declare Function SetupDiCreateDeviceInfoList _
    Lib "setupapi.dll" _
    (ByRef ClassGuid As GUID, _
    ByVal hwndParent As Long) _
As Long

Public Declare Function SetupDiDestroyDeviceInfoList _
    Lib "setupapi.dll" _
    (ByVal DeviceInfoSet As Long) _
As Long

Public Declare Function SetupDiEnumDeviceInterfaces _
    Lib "setupapi.dll" _
    (ByVal DeviceInfoSet As Long, _
    ByVal DeviceInfoData As Long, _
    ByRef InterfaceClassGuid As GUID, _
    ByVal MemberIndex As Long, _
    ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA) _
As Long

Public Declare Function SetupDiGetClassDevs _
    Lib "setupapi.dll" _
    Alias "SetupDiGetClassDevsA" _
    (ByRef ClassGuid As GUID, _
    ByVal Enumerator As String, _
    ByVal hwndParent As Long, _
    ByVal Flags As Long) _
As Long

Public Declare Function SetupDiGetDeviceInterfaceDetail _
   Lib "setupapi.dll" _
   Alias "SetupDiGetDeviceInterfaceDetailA" _
   (ByVal DeviceInfoSet As Long, _
   ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA, _
   ByVal DeviceInterfaceDetailData As Long, _
   ByVal DeviceInterfaceDetailDataSize As Long, _
   ByRef RequiredSize As Long, _
   ByVal DeviceInfoData As Long) _
As Long
    
Public Declare Function WaitForSingleObject _
    Lib "kernel32" _
    (ByVal hHandle As Long, _
    ByVal dwMilliseconds As Long) _
As Long
    
Public Declare Function WriteFile _
    Lib "kernel32" _
    (ByVal hFile As Long, _
    ByRef lpBuffer As Byte, _
    ByVal nNumberOfBytesToWrite As Long, _
    ByRef lpNumberOfBytesWritten As Long, _
    ByVal lpOverlapped As Long) _
As Long
 
Now create a VB6 form with a listbox (lstResults)

In the example I had, there was a form with

listbox (lstResults)
2 x comboboxes (cboByte1 and cboByte2)
checkbox (chkAutoincrement)
textbox (txtBytesReceived)
2 x command buttons (cmdOnce and cmdContinuous)

Here's the first bit of code from the form:
Code:
Option Explicit

Dim bAlertable As Long
Dim Capabilities As HIDP_CAPS
Dim DataString As String
Dim DetailData As Long
Dim DetailDataBuffer() As Byte
Dim DeviceAttributes As HIDD_ATTRIBUTES
Dim DevicePathName As String
Dim DeviceInfoSet As Long
Dim ErrorString As String
Dim EventObject As Long
Dim HIDHandle As Long
Dim HIDOverlapped As OVERLAPPED
Dim LastDevice As Boolean
Dim MyDeviceDetected As Boolean
Dim MyDeviceInfoData As SP_DEVINFO_DATA
Dim MyDeviceInterfaceDetailData As SP_DEVICE_INTERFACE_DETAIL_DATA
Dim MyDeviceInterfaceData As SP_DEVICE_INTERFACE_DATA
Dim Needed As Long
Dim OutputReportData(7) As Byte
Dim PreparsedData As Long
Dim ReadHandle As Long
Dim Result As Long
Dim Security As SECURITY_ATTRIBUTES
Dim Timeout As Boolean

'Set these to match the values in the device's firmware and INF file.
'0925h is Lakeview Research's vendor ID.

Const MyVendorID = &H1221
Const MyProductID = &H1234

Function FindTheHid() As Boolean

'Makes a series of API calls to locate the desired HID-class device.
'Returns True if the device is detected, False if not detected.

Dim Count As Integer
Dim GUIDString As String
Dim HidGuid As GUID
Dim MemberIndex As Long

LastDevice = False
MyDeviceDetected = False

Security.lpSecurityDescriptor = 0
Security.bInheritHandle = True
Security.nLength = Len(Security)
Result = HidD_GetHidGuid(HidGuid)
Call DisplayResultOfAPICall("GetHidGuid")

'Display the GUID.

GUIDString = _
    Hex$(HidGuid.Data1) & "-" & _
    Hex$(HidGuid.Data2) & "-" & _
    Hex$(HidGuid.Data3) & "-"

For Count = 0 To 7

    'Ensure that each of the 8 bytes in the GUID displays two characters.
    
    If HidGuid.Data4(Count) >= &H10 Then
        GUIDString = GUIDString & Hex$(HidGuid.Data4(Count)) & " "
    Else
        GUIDString = GUIDString & "0" & Hex$(HidGuid.Data4(Count)) & " "
    End If
Next Count

lstResults.AddItem "  GUID for system HIDs: " & GUIDString

DeviceInfoSet = SetupDiGetClassDevs _
    (HidGuid, _
    vbNullString, _
    0, _
    (DIGCF_PRESENT Or DIGCF_DEVICEINTERFACE))
    
Call DisplayResultOfAPICall("SetupDiClassDevs")
DataString = GetDataString(DeviceInfoSet, 32)

MemberIndex = 0

Do
    
    MyDeviceInterfaceData.cbSize = LenB(MyDeviceInterfaceData)
    Result = SetupDiEnumDeviceInterfaces _
        (DeviceInfoSet, _
        0, _
        HidGuid, _
        MemberIndex, _
        MyDeviceInterfaceData)
    
    Call DisplayResultOfAPICall("SetupDiEnumDeviceInterfaces")
    If Result = 0 Then LastDevice = True
    
    'If a device exists, display the information returned.
    
    If Result <> 0 Then
        lstResults.AddItem "  DeviceInfoSet for device #" & CStr(MemberIndex) & ": "
        lstResults.AddItem "  cbSize = " & CStr(MyDeviceInterfaceData.cbSize)
        lstResults.AddItem _
            "  InterfaceClassGuid.Data1 = " & Hex$(MyDeviceInterfaceData.InterfaceClassGuid.Data1)
        lstResults.AddItem _
            "  InterfaceClassGuid.Data2 = " & Hex$(MyDeviceInterfaceData.InterfaceClassGuid.Data2)
        lstResults.AddItem _
            "  InterfaceClassGuid.Data3 = " & Hex$(MyDeviceInterfaceData.InterfaceClassGuid.Data3)
        lstResults.AddItem _
            "  Flags = " & Hex$(MyDeviceInterfaceData.Flags)
        
        MyDeviceInfoData.cbSize = Len(MyDeviceInfoData)
        Result = SetupDiGetDeviceInterfaceDetail _
           (DeviceInfoSet, _
           MyDeviceInterfaceData, _
           0, _
           0, _
           Needed, _
           0)
        
        DetailData = Needed
            
        Call DisplayResultOfAPICall("SetupDiGetDeviceInterfaceDetail")
        lstResults.AddItem "  (OK to say too small)"
        lstResults.AddItem "  Required buffer size for the data: " & Needed
        
        'Store the structure's size.
        
        MyDeviceInterfaceDetailData.cbSize = _
            Len(MyDeviceInterfaceDetailData)
        
        ReDim DetailDataBuffer(Needed)
        
        'Store cbSize in the first four bytes of the array.
        
        Call RtlMoveMemory _
            (DetailDataBuffer(0), _
            MyDeviceInterfaceDetailData, _
            4)
        
        Result = SetupDiGetDeviceInterfaceDetail _
           (DeviceInfoSet, _
           MyDeviceInterfaceData, _
           VarPtr(DetailDataBuffer(0)), _
           DetailData, _
           Needed, _
           0)
        
        Call DisplayResultOfAPICall(" Result of second call: ")
        lstResults.AddItem "  MyDeviceInterfaceDetailData.cbSize: " & _
            CStr(MyDeviceInterfaceDetailData.cbSize)
        
        'Convert the byte array to a string.
        
        DevicePathName = CStr(DetailDataBuffer())
        
        'Convert to Unicode.
        
        DevicePathName = StrConv(DevicePathName, vbUnicode)
        
        'Strip cbSize (4 bytes) from the beginning.
        
        DevicePathName = Right$(DevicePathName, Len(DevicePathName) - 4)
        lstResults.AddItem "  Device pathname: "
        lstResults.AddItem "    " & DevicePathName
                
        HIDHandle = CreateFile _
            (DevicePathName, _
            GENERIC_READ Or GENERIC_WRITE, _
            (FILE_SHARE_READ Or FILE_SHARE_WRITE), _
            Security, _
            OPEN_EXISTING, _
            0&, _
            0)
            
        Call DisplayResultOfAPICall("CreateFile")
        lstResults.AddItem "  Returned handle: " & Hex$(HIDHandle) & "h"
        
        'Now we can find out if it's the device we're looking for.
        'Set the Size property to the number of bytes in the structure.
        
        DeviceAttributes.Size = LenB(DeviceAttributes)
        Result = HidD_GetAttributes _
            (HIDHandle, _
            DeviceAttributes)
            
        Call DisplayResultOfAPICall("HidD_GetAttributes")
        If Result <> 0 Then
            lstResults.AddItem "  HIDD_ATTRIBUTES structure filled without error."
        Else
            lstResults.AddItem "  Error in filling HIDD_ATTRIBUTES structure."
        End If
    
        lstResults.AddItem "  Structure size: " & DeviceAttributes.Size
        lstResults.AddItem "  Vendor ID: " & Hex$(DeviceAttributes.VendorID)
        lstResults.AddItem "  Product ID: " & Hex$(DeviceAttributes.ProductID)
        lstResults.AddItem "  Version Number: " & Hex$(DeviceAttributes.VersionNumber)
        
        'Find out if the device matches the one we're looking for.
        
        If (DeviceAttributes.VendorID = MyVendorID) And _
            (DeviceAttributes.ProductID = MyProductID) Then
                
                'It's the desired device.
                
                lstResults.AddItem "  My device detected"
                MyDeviceDetected = True
        Else
                MyDeviceDetected = False
                
                'If it's not the one we want, close its handle.
                
                Result = CloseHandle _
                    (HIDHandle)
                DisplayResultOfAPICall ("CloseHandle")
        End If
End If
    
    'Keep looking until we find the device or there are no more left to examine.
    
    MemberIndex = MemberIndex + 1
Loop Until (LastDevice = True) Or (MyDeviceDetected = True)

'Free the memory reserved for the DeviceInfoSet returned by SetupDiGetClassDevs.

Result = SetupDiDestroyDeviceInfoList _
    (DeviceInfoSet)
Call DisplayResultOfAPICall("DestroyDeviceInfoList")

If MyDeviceDetected = True Then
    FindTheHid = True
    
    'Learn the capabilities of the device
     
     Call GetDeviceCapabilities
    
    'Get another handle for the overlapped ReadFiles.
    
    ReadHandle = CreateFile _
            (DevicePathName, _
            (GENERIC_READ Or GENERIC_WRITE), _
            (FILE_SHARE_READ Or FILE_SHARE_WRITE), _
            Security, _
            OPEN_EXISTING, _
            FILE_FLAG_OVERLAPPED, _
            0)
 
    Call DisplayResultOfAPICall("CreateFile, ReadHandle")
    lstResults.AddItem "  Returned handle: " & Hex$(ReadHandle) & "h"
    Call PrepareForOverlappedTransfer
Else
    lstResults.AddItem " Device not found."
End If

End Function

Private Function GetDataString _
    (Address As Long, _
    Bytes As Long) _
As String

'Retrieves a string of length Bytes from memory, beginning at Address.
'Adapted from Dan Appleman's "Win32 API Puzzle Book"

Dim Offset As Integer
Dim Result$
Dim ThisByte As Byte

For Offset = 0 To Bytes - 1
    Call RtlMoveMemory(ByVal VarPtr(ThisByte), ByVal Address + Offset, 1)
    If (ThisByte And &HF0) = 0 Then
        Result$ = Result$ & "0"
    End If
    Result$ = Result$ & Hex$(ThisByte) & " "
Next Offset

GetDataString = Result$
End Function

Private Function GetErrorString _
    (ByVal LastError As Long) _
As String

'Returns the error message for the last error.
'Adapted from Dan Appleman's "Win32 API Puzzle Book"

Dim Bytes As Long
Dim ErrorString As String
ErrorString = String$(129, 0)
Bytes = FormatMessage _
    (FORMAT_MESSAGE_FROM_SYSTEM, _
    0&, _
    LastError, _
    0, _
    ErrorString$, _
    128, _
    0)
    
'Subtract two characters from the message to strip the CR and LF.

If Bytes > 2 Then
    GetErrorString = Left$(ErrorString, Bytes - 2)
End If

End Function

Private Sub cmdContinuous_Click()

'Enables the user to select 1-time or continuous data transfers.

If cmdContinuous.Caption = "Continuous" Then
    
    'Change the command button to Cancel Continuous
    
    cmdContinuous.Caption = "Cancel Continuous"
    
    'Enable the timer to read and write to the device once/second.
    
    tmrContinuousDataCollect.Enabled = True
    Call ReadAndWriteToDevice
Else
    
    'Change the command button to Continuous
    
    cmdContinuous.Caption = "Continuous"
    
    'Disable the timer that reads and writes to the device once/second.
    
    tmrContinuousDataCollect.Enabled = False
End If

End Sub

Private Sub cmdOnce_Click()
Call ReadAndWriteToDevice
End Sub

Private Sub DisplayResultOfAPICall(FunctionName As String)

'Display the results of an API call.

Dim ErrorString As String

lstResults.AddItem ""
ErrorString = GetErrorString(Err.LastDllError)
lstResults.AddItem FunctionName
lstResults.AddItem "  Result = " & ErrorString

'Scroll to the bottom of the list box.

lstResults.ListIndex = lstResults.ListCount - 1

End Sub
 
DLL-free way to talk to USB: part 2

Here's the second part of the code to go in the form.
(Continues from the code in an earlier reply to this post)
Code:
Private Sub Form_Load()
frmMain.Show
tmrDelay.Enabled = False
Call Startup
End Sub

Private Sub Form_Unload(Cancel As Integer)
Call Shutdown
End Sub

Private Sub GetDeviceCapabilities()

Dim ppData(29) As Byte
Dim ppDataString As Variant

'Preparsed Data is a pointer to a routine-allocated buffer.

Result = HidD_GetPreparsedData _
    (HIDHandle, _
    PreparsedData)
Call DisplayResultOfAPICall("HidD_GetPreparsedData")

'Copy the data at PreparsedData into a byte array.

Result = RtlMoveMemory _
    (ppData(0), _
    PreparsedData, _
    30)
Call DisplayResultOfAPICall("RtlMoveMemory")

ppDataString = ppData()

'Convert the data to Unicode.

ppDataString = StrConv(ppDataString, vbUnicode)

Result = HidP_GetCaps _
    (PreparsedData, _
    Capabilities)

Call DisplayResultOfAPICall("HidP_GetCaps")
lstResults.AddItem "  Last error: " & ErrorString
lstResults.AddItem "  Usage: " & Hex$(Capabilities.Usage)
lstResults.AddItem "  Usage Page: " & Hex$(Capabilities.UsagePage)
lstResults.AddItem "  Input Report Byte Length: " & Capabilities.InputReportByteLength
lstResults.AddItem "  Output Report Byte Length: " & Capabilities.OutputReportByteLength
lstResults.AddItem "  Feature Report Byte Length: " & Capabilities.FeatureReportByteLength
lstResults.AddItem "  Number of Link Collection Nodes: " & Capabilities.NumberLinkCollectionNodes
lstResults.AddItem "  Number of Input Button Caps: " & Capabilities.NumberInputButtonCaps
lstResults.AddItem "  Number of Input Value Caps: " & Capabilities.NumberInputValueCaps
lstResults.AddItem "  Number of Input Data Indices: " & Capabilities.NumberInputDataIndices
lstResults.AddItem "  Number of Output Button Caps: " & Capabilities.NumberOutputButtonCaps
lstResults.AddItem "  Number of Output Value Caps: " & Capabilities.NumberOutputValueCaps
lstResults.AddItem "  Number of Output Data Indices: " & Capabilities.NumberOutputDataIndices
lstResults.AddItem "  Number of Feature Button Caps: " & Capabilities.NumberFeatureButtonCaps
lstResults.AddItem "  Number of Feature Value Caps: " & Capabilities.NumberFeatureValueCaps
lstResults.AddItem "  Number of Feature Data Indices: " & Capabilities.NumberFeatureDataIndices


'This is a guess. The byte array holds the structures.

Dim ValueCaps(1023) As Byte

Result = HidP_GetValueCaps _
    (HidP_Input, _
    ValueCaps(0), _
    Capabilities.NumberInputValueCaps, _
    PreparsedData)
   
Call DisplayResultOfAPICall("HidP_GetValueCaps")

Result = HidD_FreePreparsedData _
    (PreparsedData)
Call DisplayResultOfAPICall("HidD_FreePreparsedData")

End Sub

Private Sub InitializeDisplay()
Dim Count As Integer
Dim ByteValue As String

'Create a dropdown list box for each byte to send.

For Count = 0 To 255
    If Len(Hex$(Count)) < 2 Then
        ByteValue = "0" & Hex$(Count)
    Else
        ByteValue = Hex$(Count)
    End If
    frmMain.cboByte0.AddItem ByteValue, Count
Next Count

For Count = 0 To 255
    If Len(Hex$(Count)) < 2 Then
        ByteValue = "0" & Hex$(Count)
    Else
        ByteValue = Hex$(Count)
    End If
    frmMain.cboByte1.AddItem ByteValue, Count
Next Count

'Select a default item for each box

frmMain.cboByte0.ListIndex = 0
frmMain.cboByte1.ListIndex = 128

chkAutoincrement.Value = 1
End Sub

Private Sub PrepareForOverlappedTransfer()

If EventObject = 0 Then
    EventObject = CreateEvent _
        (Security, _
        True, _
        True, _
        "")
End If
    
Call DisplayResultOfAPICall("CreateEvent")
    
'Set the members of the overlapped structure.

HIDOverlapped.Offset = 0
HIDOverlapped.OffsetHigh = 0
HIDOverlapped.hEvent = EventObject
End Sub

Private Sub ReadAndWriteToDevice()

'Sends two bytes to the device and reads two bytes back.

Dim Count As Integer

'Report Header

lstResults.AddItem ""
lstResults.AddItem "***** HID Test Report *****"
lstResults.AddItem Format(Now, "general date")

'Some data to send
'(if not using the combo boxes):
OutputReportData(0) = &H12
OutputReportData(1) = &H34
OutputReportData(2) = &HF0
OutputReportData(3) = &HF1
OutputReportData(4) = &HF2
OutputReportData(5) = &HF3
OutputReportData(6) = &HF4
OutputReportData(7) = &HF5

'If the device hasn't been detected or it timed out on a previous attempt
'to access it, look for the device.

If MyDeviceDetected = False Then
    MyDeviceDetected = FindTheHid
    
End If

If MyDeviceDetected = True Then

    'Get the bytes to send from the combo boxes.
    'Increment the values if the autoincrement check box is selected.
    
    If chkAutoincrement.Value = 1 Then
        If cboByte0.ListIndex < 255 Then
            cboByte0.ListIndex = cboByte0.ListIndex + 1
        Else
            cboByte0.ListIndex = 0
        End If
        If cboByte1.ListIndex < 255 Then
            cboByte1.ListIndex = cboByte1.ListIndex + 1
        Else
            cboByte1.ListIndex = 0
        End If
    End If
    
    OutputReportData(0) = cboByte0.ListIndex
    OutputReportData(1) = cboByte1.ListIndex
       
    'Write a report to the device
    
    Call WriteReport
    
    'Read a report from the device.
    
    Call ReadReport
Else
End If

'Scroll to the bottom of the list box.

lstResults.ListIndex = lstResults.ListCount - 1

'If the list box has more than 300 items, trim the contents.

If lstResults.ListCount > 300 Then
    For Count = 1 To 100
        lstResults.RemoveItem (Count)
    Next Count
End If

End Sub

Private Sub ReadReport()

'Read data from the device.

Dim Count
Dim NumberOfBytesRead As Long

'Allocate a buffer for the report.
'Byte 0 is the report ID.

Dim ReadBuffer() As Byte
Dim UBoundReadBuffer As Integer
Dim ByteValue As String

'The ReadBuffer array begins at 0, so subtract 1 from the number of bytes.

ReDim ReadBuffer(Capabilities.InputReportByteLength - 1)

'Scroll to the bottom of the list box.

lstResults.ListIndex = lstResults.ListCount - 1

'Do an overlapped ReadFile.
'The function returns immediately, even if the data hasn't been received yet.

Result = ReadFile _
    (ReadHandle, _
    ReadBuffer(0), _
    CLng(Capabilities.InputReportByteLength), _
    NumberOfBytesRead, _
    HIDOverlapped)
Call DisplayResultOfAPICall("ReadFile")

lstResults.AddItem "waiting for ReadFile"

'Scroll to the bottom of the list box.

lstResults.ListIndex = lstResults.ListCount - 1
bAlertable = True

Result = WaitForSingleObject _
    (EventObject, _
    6000)
Call DisplayResultOfAPICall("WaitForSingleObject")

'Find out if ReadFile completed or timeout.

Select Case Result
    Case WAIT_OBJECT_0
        
        'ReadFile has completed
        
        lstResults.AddItem "ReadFile completed successfully."
    Case WAIT_TIMEOUT
        
        'Timeout
        
        lstResults.AddItem "Readfile timeout"
        Result = CancelIo _
            (ReadHandle)
        lstResults.AddItem "************ReadFile timeout*************"
        lstResults.AddItem "CancelIO"
        Call DisplayResultOfAPICall("CancelIo")
        
        CloseHandle (HIDHandle)
        Call DisplayResultOfAPICall("CloseHandle (HIDHandle)")
        CloseHandle (ReadHandle)
        Call DisplayResultOfAPICall("CloseHandle (ReadHandle)")
        MyDeviceDetected = False
    Case Else
        lstResults.AddItem "Readfile undefined error"
        MyDeviceDetected = False
End Select
    
lstResults.AddItem " Report ID: " & ReadBuffer(0)
lstResults.AddItem " Report Data:"

txtBytesReceived.Text = ""
For Count = 1 To UBound(ReadBuffer)
    
    'Add a leading 0 to values 0 - Fh.
    
    If Len(Hex$(ReadBuffer(Count))) < 2 Then
        ByteValue = "0" & Hex$(ReadBuffer(Count))
    Else
        ByteValue = Hex$(ReadBuffer(Count))
    End If
    
    lstResults.AddItem " " & ByteValue
    
    'Display the received bytes in the text box.
    
    txtBytesReceived.SelStart = Len(txtBytesReceived.Text)
    txtBytesReceived.SelText = ByteValue & vbCrLf

Next Count

Call ResetEvent(EventObject)
Call DisplayResultOfAPICall("ResetEvent")

End Sub

Private Sub Shutdown()

Result = CloseHandle _
    (HIDHandle)
Call DisplayResultOfAPICall("CloseHandle (HIDHandle)")

Result = CloseHandle _
    (ReadHandle)
Call DisplayResultOfAPICall("CloseHandle (ReadHandle)")

End Sub

Private Sub Startup()

Call InitializeDisplay
tmrContinuousDataCollect.Enabled = False
tmrContinuousDataCollect.Interval = 1000

End Sub

Private Sub tmrContinuousDataCollect_Timer()
Call ReadAndWriteToDevice

End Sub

Private Sub tmrDelay_Timer()

Timeout = True
tmrDelay.Enabled = False

End Sub

Private Sub WriteReport()

'Send data to the device.

Dim Count As Integer
Dim NumberOfBytesRead As Long
Dim NumberOfBytesToSend As Long
Dim NumberOfBytesWritten As Long
Dim ReadBuffer() As Byte
Dim SendBuffer() As Byte
ReDim SendBuffer(Capabilities.OutputReportByteLength - 1)

'The first byte is the Report ID
SendBuffer(0) = 0

'The next bytes are data
For Count = 1 To Capabilities.OutputReportByteLength - 1
    SendBuffer(Count) = OutputReportData(Count - 1)
Next Count

NumberOfBytesWritten = 0

Result = WriteFile _
    (HIDHandle, _
    SendBuffer(0), _
    CLng(Capabilities.OutputReportByteLength), _
    NumberOfBytesWritten, _
    0)
Call DisplayResultOfAPICall("WriteFile")

lstResults.AddItem " OutputReportByteLength = " & Capabilities.OutputReportByteLength
lstResults.AddItem " NumberOfBytesWritten = " & NumberOfBytesWritten
lstResults.AddItem " Report ID: " & SendBuffer(0)
lstResults.AddItem " Report Data:"

For Count = 1 To UBound(SendBuffer)
    lstResults.AddItem " " & Hex$(SendBuffer(Count))
Next Count

End Sub

Hope this helps. I used a variation on the code myself a while ago. From what I remember, it's pretty easy to amend for your own needs....
 
Jan Axelson HID page
**broken link removed**

My VB USB Template modified and hosted by HelmPCB
**broken link removed**
 
Status
Not open for further replies.

Latest threads

New Articles From Microcontroller Tips

Back
Top