Accessing Type Libraries from VB



December 01, 1999
URL:http://www.drdobbs.com/accessing-type-libraries-from-vb/184416565

December 1999/Accessing Type Libraries from VB


Type libraries provide meta information about libraries: the names of functions, their parameters, and so on. Microsoft provides low-level interfaces that let programs browse and even create type libraries. There are a number of uses for this ability. For example, you might want to create a custom user interface for browsing or maintaining type libraries. In another example, a program that can be extended with custom COM objects might want to programmatically inspect the type library of a DLL before calling it directly, just to ensure that it conforms to certain specifications. C++ is typically used to access the low-level interfaces Microsoft provides for type libraries, but this article will demonstrate that you can get at type libraries directly from VB without using C++ at all.

VB ships with tlbinf32.dll, which gives VB programs an interface for accessing type libraries. Though this file is undocumented and unsupported by Microsoft, you can redistribute it with your own projects (see license.txt and redist.txt in the VB5 or VB6 folder). See Knowledge Base article Q172988 for the official word. (Point your browser at http://support.microsoft.com/support/kb/articles/Q172/9/88.asp or email [email protected] with a subject line of “Q172988”.) The only other references to this file in the MSDN library are in the books section under “Advanced Microsoft Visual Basic 5” in chapter 8 and “Hardcore Visual Basic” in chapter 10, and that information is limited.

A Sample Program

To demonstrate using type library information from Visual Basic, I first wrote a simple COM server (comservr.vbp in this month’s code archive). This COM server exposes three properties: Interest is a Double that specifies an interest rate (e.g., 0.095 for 9.5%); Term is a Long that contains the length of a loan in months; and Amount is a Currency variable that contains the dollar amount of the loan. The server also exposes three methods:

Function calculatePayment1 () As Currency
Function calculatePayment2 (dInterest As Double, _
     LTerm As Long, _
     CAmount As Currency) As Currency
Function calculatePayment3 (Optional dInterest As Double, _
     Optional lTerm As Long,  _
     Optional cAmount As Currency) As Currency

All the methods return the monthly payment amount.

This simple COM server provides some dummy code whose type library information you can inspect. Run comservr.exe once to register the program for use. Don’t forget to type

COMServr /unregserver

before deleting the .exe, to ensure that the associated registry entries get removed.

The second program (in project typeinfo.vbp in this month’s code archive) uses the simplified type library interface that tlbinf32.dll provides to let you display type library information. The main source code is in typeinfo.bas (Listing 1), and some less important functions are in typemisc.bas in this month’s code archive. You can execute typeinfo.exe and then either enter the COM name (e.g., COMServr.clsLoanPayment) or select the file name (e.g., comservr.exe) of the object/file containing the type library information you want to display. Note that you may enter the COM name only for objects Visual Basic can dynamically load using CreateObject(); typically OCXs will not work here. You may still get type library information from an OCX file (or any file with a type library) using TypeLibInfoFromFile, you just won’t be able to invoke any of its methods. For an example of an OCX that does work, try MSComDlg.CommonDialog or comdlg32.ocx.

Once you load the object, the program displays the method names and return types (functions and property get/puts) in a treeview control. To reduce clutter, the program avoids displaying standard COM methods such as QueryInterface() and AddRef(). typeinfo.exe gets this information from the MemberInfo property by looping through the Members collection of the InterfaceInfo property. The member ID is saved in the treeview nodes’ Tag property, so it is readily available should the user invoke the method. The dash is important in the treeview node’s Text property as the program uses it to differentiate between methods and parameters. If a method has any parameters, their name and type are displayed in treeview child nodes of the method node. This information is retrieved from the Parameters collection of the MemberInfo property. The parameter type is saved in the treeview nodes’ Tag property so it is handy for the invoke method.

To test the calculatePayment1 method, double-click the “Interest - Property Put” item and enter a value. Do the same for the Term and Amount properties and then double click the caclulatePayment1 method to get the result. To verify properties are set just double-click the properties’ “Property Get” item and the current value will be displayed. For methods with parameters like calculatePayment2, you are prompted (sorry, I used InputBox to keep the program size down) for the parameter(s) and then the method is invoked and the return value displayed.

The calculatePayment3 method demonstrates how to handle optional parameters — if you don’t enter anything when prompted for a value, typeinfo.exe assumes this is an optional parameter and removes the array entry that will be passed to InvokeHookArray. Be aware this means that if you aren’t passing the second parameter, you may not pass the third. Also note that this array is zero-based and InvokeHookArray expects the parameters in reverse order. A property put uses the InvokeHook method as there is only one parameter, as does the property get which has no parameters. The InvokeHook method requires that you specify the parameters in the same order as the method expects them and is not as useful for dynamic method invocation.

More Information

If you’ve never dealt with type library information before, be prepared for confusion. The tlbinf32.dll object model does hide a lot of the messy details, but you’ll notice the same information is available in one or more different ways — which models the underlying COM type library interfaces. Hopefully Microsoft will decide to document this useful object more completely in the near future. For further reading on type library information, see Inside OLE by Craig Brockschmidt, especially chapter three which discusses the ITypeLib, ITypeInfo, and IProvideClassInfo COM interfaces. If you have MSDN, see the Interfaces section under Platform, SDK and DDK Documentation | Object Services | COM | Reference.

Microsoft’s home page for COM information is currently http://www.microsoft.com/com/. If you look there for specifications under the Resources heading, you can find a page that lets you download a copy of the COM specifications. Unfortunately it does not contain the type library information section! The information missing there is currently available as part of the Win32 Platform SDK, however. Go to http://msdn.microsoft.com, click on “Products”, then click on “Microsoft Platform SDK”. If you have Win98 or NT 4, you should be able to download the latest version of the SDK (though you may have to first download an updated version of Windows Installer). Unless you have a very fast network connection, you will probably want to download just a subset of the SDK. The documentation for COM is the portion that has the type library information. Once you download that, you should end up with a file named something like Platform SDK/help/automat.chm, which is the HTML Help file that documents OLE automation, which includes the type library interface documentation.

William R. Epp is an IM Consultant for Neutrogena, a proud member of the Johnson & Johnson family of companies (i.e., that Uncle no one talks about). Feel free to send praise, cash, or glowing comments to [email protected].

Get Source Code

December 1999/Accessing Type Libraries from VB/Listing 1

Listing 1: typeinfo.bas — Code to browse type libraries

Attribute VB_Name = "basTypeInfo"
Option Explicit
Public Sub invoke(nSelected As Node, obj As Object)

    Dim iDash As Integer
    Dim iParmIndx As Integer
    Dim iNbrParms As Integer
    
    Dim sMethod As String
    Dim sParmValue As String
    
    Dim vParm As Variant
    
    Dim vaParms() As Variant
    
    Dim nChild As Node
    
    Dim ii As InterfaceInfo
    
    Dim mi As MemberInfo
    
    Dim tli As TLIApplication
    
'/* error trapping */
    On Error GoTo invoke_error
    
    Set tli = New TLIApplication
    
'/* methods/properties always delimited with a dash */
    sMethod = nSelected.Text
    iDash = InStr(sMethod, "-")
    If iDash > 0 Then
        
        sMethod = Trim$(Left$(sMethod, iDash - 1))
        
        Set ii = tli.InterfaceInfoFromObject(obj)
        
    '/* get member by id */
    '/* (tag set in loadTreeViewWithClassInfo) */
        Set mi = ii.Members.Item(nSelected.Tag)
        
        Select Case mi.InvokeKind
                
            Case INVOKE_FUNC
                
                iNbrParms = mi.Parameters.Count
                If iNbrParms > 0 Then
                    
                    ReDim vaParms(iNbrParms - 1)
                    
                '/* there is one child item in treeview */
                '/* for each invoke method parameter */
                    Set nChild = nSelected.Child
                    For iParmIndx = 1 To nSelected.Children
                        
                        sParmValue = InputBox( _
                                     "Enter Parameter Value " & _
                                     nChild.Text)
                        
                    '/* blank - assume optional and remove */
                        If Trim$(sParmValue) = "" Then
                            ReDim Preserve vaParms(iNbrParms - 1)
                            
                        Else
                        '/* set parameter type */
                        '/* (tag set in loadTreeViewWithClassInfo) */
                            vaParms(iNbrParms - 1) = _
                                setType(sParmValue, nChild.Tag)
                        End If
                        
                    '/* in reverse order! */
                        iNbrParms = iNbrParms - 1
                        Set nChild = nChild.Next
                        
                    Next iParmIndx
                    
                    vParm = tli.InvokeHookArray(obj, sMethod, _
                                        INVOKE_FUNC, vaParms())
                Else
                    
                '/* no parameters */
                    vParm = tli.InvokeHook(obj, sMethod, _
                                           INVOKE_FUNC)
                End If
                
                MsgBox "Return =  " & vParm
                
            Case INVOKE_PROPERTYPUT
                
                sParmValue = InputBox( _
                             "Enter Value for Property ", _
                             "Property Put")
                
                If sParmValue <> "" Then
                    vParm = setType(sParmValue, mi.ReturnType)
                    Call tli.InvokeHook(obj, sMethod, _
                                        INVOKE_PROPERTYPUT, vParm)
                End If
                
            Case INVOKE_PROPERTYGET
                
                vParm = tli.InvokeHook(obj, sMethod, _
                                 INVOKE_PROPERTYGET)
                MsgBox "Property Value = " & vParm
                
        End Select
    End If
    
invoke_exit:
    Set mi = Nothing
    Set ii = Nothing
    Set tli = Nothing
    Exit Sub
    
invoke_error:
    MsgBox Err.Number & " : " & Err.Description & " (invoke)"
    Resume invoke_exit
    
End Sub
    
Public Function loadListboxWithClassNames(sFilename As String, _
                                          lstClasses As ListBox) _
                                          As String
    
    Dim iTypeIndx As Integer
    
    Dim sRetInfo As String
    
    Dim ti As TypeLibInfo
    
    Dim tli As TLIApplication
    
'/* error trapping */
    On Error GoTo loadListboxWithClassNames_error
    
    Set tli = New TLIApplication
    Set ti = New TypeLibInfo
    
    Set ti = tli.TypeLibInfoFromFile(sFilename)
    sRetInfo = ti.Guid & "  " & ti.MajorVersion & "." & _
               ti.MinorVersion
    
    lstClasses.Clear
    For iTypeIndx = 1 To ti.TypeInfoCount
        
    '/* only classes - ignore anything else */
        If ti.TypeInfos.Item(iTypeIndx).TypeKind = _
                TKIND_COCLASS Then
            lstClasses.AddItem ti.Name & "." & _
                               ti.TypeInfos.Item(iTypeIndx).Name
        End If
    Next iTypeIndx
    
loadListboxWithClassNames_exit:
    Set ti = Nothing
    Set tli = Nothing
    
'/* return */
    loadListboxWithClassNames = sRetInfo
    Exit Function
    
loadListboxWithClassNames_error:
    MsgBox Err.Number & " : " & Err.Description & _
           " (loadListboxWithClassNames)"
    Resume loadListboxWithClassNames_exit
    
End Function
    
Public Function loadTreeviewWithClassInfo(sCOMName As String, _
                                          tvwClasses As TreeView) _
                                          As String
    
    Dim iMemberIndx As Integer
    Dim iNbrMembers As Integer
    Dim iParameterIndx As Integer
    Dim iTreeviewIndx As Integer
    Dim iSaveIndx As Integer
    Dim iNbrParms As Integer
    Dim iMemberID As Integer
    
    Dim sRetInfo As String
    
    Dim obj As Object
    
    Dim n As Node
    
    Dim ii As InterfaceInfo
    
    Dim mi As MemberInfo
    
    Dim ti As TypeLibInfo
    
    Dim tli As TLIApplication
    
'/* error trapping */
    On Error GoTo loadTreeviewWithClassInfo_error
    
    Set obj = CreateObject(sCOMName)
    
    Set tli = New TLIApplication
    
    Set ti = New TypeLibInfo
    
    Set ii = tli.InterfaceInfoFromObject(obj)
    
    iNbrMembers = ii.Members.Count
    
    Set ti = ii.Parent
    sRetInfo = ti.Guid & "  " & ti.MajorVersion & "." & _
               ti.MinorVersion
    
    tvwClasses.Nodes.Clear
    tvwClasses.Nodes.Add , , , Mid$(ii.Name, 2)
    
'/* treeview index, assign to each node sequentially */
    iTreeviewIndx = 1
'/* type lib id for method, ie. function or property get/put */
    iMemberID = 0
    
    For iMemberIndx = 1 To iNbrMembers
        
        Set mi = ii.Members.Item(iMemberIndx)
        iMemberID = iMemberID + 1
        
        If Not ignoreName(mi.Name) Then
            
        '/* method name, method type and return type */
            tvwClasses.Nodes.Add 1, tvwChild, , mi.Name & " - " & _
            getInvokeKindsName(mi.InvokeKind) & _
                " (" & getVTTypeName(mi.ReturnType) & ")"
            
            iTreeviewIndx = iTreeviewIndx + 1
            
        '/* save member id - see InvokeHook logic */
            tvwClasses.Nodes.Item(iTreeviewIndx).Tag = iMemberID
            
            iNbrParms = mi.Parameters.Count
            
            iSaveIndx = iTreeviewIndx
            For iParameterIndx = 1 To iNbrParms
                
            '/* parameter name and type as child node of method */
                tvwClasses.Nodes.Add iSaveIndx, tvwChild, , _
                    mi.Parameters.Item(iParameterIndx).Name & _
                    " (" & getVTTypeName(mi.Parameters.Item _
                    (iParameterIndx).VarTypeInfo) & ")"
                
                iTreeviewIndx = iTreeviewIndx + 1
                
            '/* save parameter type - see InvokeHook logic */
                tvwClasses.Nodes.Item(iTreeviewIndx).Tag = _
                    mi.Parameters(iParameterIndx).VarTypeInfo
                
            Next iParameterIndx
            
        End If
        
    Next iMemberIndx
    
    tvwClasses.Nodes(1).Expanded = True
    
loadTreeviewWithClassInfo_exit:
    Set mi = Nothing
    Set ii = Nothing
    Set ti = Nothing
    Set tli = Nothing
    Set obj = Nothing
    
'/* return */
    loadTreeviewWithClassInfo = sRetInfo
    Exit Function
    
    
loadTreeviewWithClassInfo_error:
    MsgBox Err.Number & " : " & Err.Description & _
           " (loadTreeviewWithClassInfo)"
    Resume loadTreeviewWithClassInfo_exit
    
End Function
December 1999/Accessing Type Libraries from VB

Accessing Type Libraries from VB

William R. Epp


Type libraries provide meta information about libraries: the names of functions, their parameters, and so on. Microsoft provides low-level interfaces that let programs browse and even create type libraries. There are a number of uses for this ability. For example, you might want to create a custom user interface for browsing or maintaining type libraries. In another example, a program that can be extended with custom COM objects might want to programmatically inspect the type library of a DLL before calling it directly, just to ensure that it conforms to certain specifications. C++ is typically used to access the low-level interfaces Microsoft provides for type libraries, but this article will demonstrate that you can get at type libraries directly from VB without using C++ at all.

VB ships with tlbinf32.dll, which gives VB programs an interface for accessing type libraries. Though this file is undocumented and unsupported by Microsoft, you can redistribute it with your own projects (see license.txt and redist.txt in the VB5 or VB6 folder). See Knowledge Base article Q172988 for the official word. (Point your browser at http://support.microsoft.com/support/kb/articles/Q172/9/88.asp or email [email protected] with a subject line of “Q172988”.) The only other references to this file in the MSDN library are in the books section under “Advanced Microsoft Visual Basic 5” in chapter 8 and “Hardcore Visual Basic” in chapter 10, and that information is limited.

A Sample Program

To demonstrate using type library information from Visual Basic, I first wrote a simple COM server (comservr.vbp in this month’s code archive). This COM server exposes three properties: Interest is a Double that specifies an interest rate (e.g., 0.095 for 9.5%); Term is a Long that contains the length of a loan in months; and Amount is a Currency variable that contains the dollar amount of the loan. The server also exposes three methods:

Function calculatePayment1 () As Currency
Function calculatePayment2 (dInterest As Double, _
     LTerm As Long, _
     CAmount As Currency) As Currency
Function calculatePayment3 (Optional dInterest As Double, _
     Optional lTerm As Long,  _
     Optional cAmount As Currency) As Currency

All the methods return the monthly payment amount.

This simple COM server provides some dummy code whose type library information you can inspect. Run comservr.exe once to register the program for use. Don’t forget to type

COMServr /unregserver

before deleting the .exe, to ensure that the associated registry entries get removed.

The second program (in project typeinfo.vbp in this month’s code archive) uses the simplified type library interface that tlbinf32.dll provides to let you display type library information. The main source code is in typeinfo.bas (Listing 1), and some less important functions are in typemisc.bas in this month’s code archive. You can execute typeinfo.exe and then either enter the COM name (e.g., COMServr.clsLoanPayment) or select the file name (e.g., comservr.exe) of the object/file containing the type library information you want to display. Note that you may enter the COM name only for objects Visual Basic can dynamically load using CreateObject(); typically OCXs will not work here. You may still get type library information from an OCX file (or any file with a type library) using TypeLibInfoFromFile, you just won’t be able to invoke any of its methods. For an example of an OCX that does work, try MSComDlg.CommonDialog or comdlg32.ocx.

Once you load the object, the program displays the method names and return types (functions and property get/puts) in a treeview control. To reduce clutter, the program avoids displaying standard COM methods such as QueryInterface() and AddRef(). typeinfo.exe gets this information from the MemberInfo property by looping through the Members collection of the InterfaceInfo property. The member ID is saved in the treeview nodes’ Tag property, so it is readily available should the user invoke the method. The dash is important in the treeview node’s Text property as the program uses it to differentiate between methods and parameters. If a method has any parameters, their name and type are displayed in treeview child nodes of the method node. This information is retrieved from the Parameters collection of the MemberInfo property. The parameter type is saved in the treeview nodes’ Tag property so it is handy for the invoke method.

To test the calculatePayment1 method, double-click the “Interest - Property Put” item and enter a value. Do the same for the Term and Amount properties and then double click the caclulatePayment1 method to get the result. To verify properties are set just double-click the properties’ “Property Get” item and the current value will be displayed. For methods with parameters like calculatePayment2, you are prompted (sorry, I used InputBox to keep the program size down) for the parameter(s) and then the method is invoked and the return value displayed.

The calculatePayment3 method demonstrates how to handle optional parameters — if you don’t enter anything when prompted for a value, typeinfo.exe assumes this is an optional parameter and removes the array entry that will be passed to InvokeHookArray. Be aware this means that if you aren’t passing the second parameter, you may not pass the third. Also note that this array is zero-based and InvokeHookArray expects the parameters in reverse order. A property put uses the InvokeHook method as there is only one parameter, as does the property get which has no parameters. The InvokeHook method requires that you specify the parameters in the same order as the method expects them and is not as useful for dynamic method invocation.

More Information

If you’ve never dealt with type library information before, be prepared for confusion. The tlbinf32.dll object model does hide a lot of the messy details, but you’ll notice the same information is available in one or more different ways — which models the underlying COM type library interfaces. Hopefully Microsoft will decide to document this useful object more completely in the near future. For further reading on type library information, see Inside OLE by Craig Brockschmidt, especially chapter three which discusses the ITypeLib, ITypeInfo, and IProvideClassInfo COM interfaces. If you have MSDN, see the Interfaces section under Platform, SDK and DDK Documentation | Object Services | COM | Reference.

Microsoft’s home page for COM information is currently http://www.microsoft.com/com/. If you look there for specifications under the Resources heading, you can find a page that lets you download a copy of the COM specifications. Unfortunately it does not contain the type library information section! The information missing there is currently available as part of the Win32 Platform SDK, however. Go to http://msdn.microsoft.com, click on “Products”, then click on “Microsoft Platform SDK”. If you have Win98 or NT 4, you should be able to download the latest version of the SDK (though you may have to first download an updated version of Windows Installer). Unless you have a very fast network connection, you will probably want to download just a subset of the SDK. The documentation for COM is the portion that has the type library information. Once you download that, you should end up with a file named something like Platform SDK/help/automat.chm, which is the HTML Help file that documents OLE automation, which includes the type library interface documentation.

William R. Epp is an IM Consultant for Neutrogena, a proud member of the Johnson & Johnson family of companies (i.e., that Uncle no one talks about). Feel free to send praise, cash, or glowing comments to [email protected].

Get Source Code

December 1999/Accessing Type Libraries from VB/Listing 1

Listing 1: typeinfo.bas — Code to browse type libraries

Attribute VB_Name = "basTypeInfo"
Option Explicit
Public Sub invoke(nSelected As Node, obj As Object)

    Dim iDash As Integer
    Dim iParmIndx As Integer
    Dim iNbrParms As Integer
    
    Dim sMethod As String
    Dim sParmValue As String
    
    Dim vParm As Variant
    
    Dim vaParms() As Variant
    
    Dim nChild As Node
    
    Dim ii As InterfaceInfo
    
    Dim mi As MemberInfo
    
    Dim tli As TLIApplication
    
'/* error trapping */
    On Error GoTo invoke_error
    
    Set tli = New TLIApplication
    
'/* methods/properties always delimited with a dash */
    sMethod = nSelected.Text
    iDash = InStr(sMethod, "-")
    If iDash > 0 Then
        
        sMethod = Trim$(Left$(sMethod, iDash - 1))
        
        Set ii = tli.InterfaceInfoFromObject(obj)
        
    '/* get member by id */
    '/* (tag set in loadTreeViewWithClassInfo) */
        Set mi = ii.Members.Item(nSelected.Tag)
        
        Select Case mi.InvokeKind
                
            Case INVOKE_FUNC
                
                iNbrParms = mi.Parameters.Count
                If iNbrParms > 0 Then
                    
                    ReDim vaParms(iNbrParms - 1)
                    
                '/* there is one child item in treeview */
                '/* for each invoke method parameter */
                    Set nChild = nSelected.Child
                    For iParmIndx = 1 To nSelected.Children
                        
                        sParmValue = InputBox( _
                                     "Enter Parameter Value " & _
                                     nChild.Text)
                        
                    '/* blank - assume optional and remove */
                        If Trim$(sParmValue) = "" Then
                            ReDim Preserve vaParms(iNbrParms - 1)
                            
                        Else
                        '/* set parameter type */
                        '/* (tag set in loadTreeViewWithClassInfo) */
                            vaParms(iNbrParms - 1) = _
                                setType(sParmValue, nChild.Tag)
                        End If
                        
                    '/* in reverse order! */
                        iNbrParms = iNbrParms - 1
                        Set nChild = nChild.Next
                        
                    Next iParmIndx
                    
                    vParm = tli.InvokeHookArray(obj, sMethod, _
                                        INVOKE_FUNC, vaParms())
                Else
                    
                '/* no parameters */
                    vParm = tli.InvokeHook(obj, sMethod, _
                                           INVOKE_FUNC)
                End If
                
                MsgBox "Return =  " & vParm
                
            Case INVOKE_PROPERTYPUT
                
                sParmValue = InputBox( _
                             "Enter Value for Property ", _
                             "Property Put")
                
                If sParmValue <> "" Then
                    vParm = setType(sParmValue, mi.ReturnType)
                    Call tli.InvokeHook(obj, sMethod, _
                                        INVOKE_PROPERTYPUT, vParm)
                End If
                
            Case INVOKE_PROPERTYGET
                
                vParm = tli.InvokeHook(obj, sMethod, _
                                 INVOKE_PROPERTYGET)
                MsgBox "Property Value = " & vParm
                
        End Select
    End If
    
invoke_exit:
    Set mi = Nothing
    Set ii = Nothing
    Set tli = Nothing
    Exit Sub
    
invoke_error:
    MsgBox Err.Number & " : " & Err.Description & " (invoke)"
    Resume invoke_exit
    
End Sub
    
Public Function loadListboxWithClassNames(sFilename As String, _
                                          lstClasses As ListBox) _
                                          As String
    
    Dim iTypeIndx As Integer
    
    Dim sRetInfo As String
    
    Dim ti As TypeLibInfo
    
    Dim tli As TLIApplication
    
'/* error trapping */
    On Error GoTo loadListboxWithClassNames_error
    
    Set tli = New TLIApplication
    Set ti = New TypeLibInfo
    
    Set ti = tli.TypeLibInfoFromFile(sFilename)
    sRetInfo = ti.Guid & "  " & ti.MajorVersion & "." & _
               ti.MinorVersion
    
    lstClasses.Clear
    For iTypeIndx = 1 To ti.TypeInfoCount
        
    '/* only classes - ignore anything else */
        If ti.TypeInfos.Item(iTypeIndx).TypeKind = _
                TKIND_COCLASS Then
            lstClasses.AddItem ti.Name & "." & _
                               ti.TypeInfos.Item(iTypeIndx).Name
        End If
    Next iTypeIndx
    
loadListboxWithClassNames_exit:
    Set ti = Nothing
    Set tli = Nothing
    
'/* return */
    loadListboxWithClassNames = sRetInfo
    Exit Function
    
loadListboxWithClassNames_error:
    MsgBox Err.Number & " : " & Err.Description & _
           " (loadListboxWithClassNames)"
    Resume loadListboxWithClassNames_exit
    
End Function
    
Public Function loadTreeviewWithClassInfo(sCOMName As String, _
                                          tvwClasses As TreeView) _
                                          As String
    
    Dim iMemberIndx As Integer
    Dim iNbrMembers As Integer
    Dim iParameterIndx As Integer
    Dim iTreeviewIndx As Integer
    Dim iSaveIndx As Integer
    Dim iNbrParms As Integer
    Dim iMemberID As Integer
    
    Dim sRetInfo As String
    
    Dim obj As Object
    
    Dim n As Node
    
    Dim ii As InterfaceInfo
    
    Dim mi As MemberInfo
    
    Dim ti As TypeLibInfo
    
    Dim tli As TLIApplication
    
'/* error trapping */
    On Error GoTo loadTreeviewWithClassInfo_error
    
    Set obj = CreateObject(sCOMName)
    
    Set tli = New TLIApplication
    
    Set ti = New TypeLibInfo
    
    Set ii = tli.InterfaceInfoFromObject(obj)
    
    iNbrMembers = ii.Members.Count
    
    Set ti = ii.Parent
    sRetInfo = ti.Guid & "  " & ti.MajorVersion & "." & _
               ti.MinorVersion
    
    tvwClasses.Nodes.Clear
    tvwClasses.Nodes.Add , , , Mid$(ii.Name, 2)
    
'/* treeview index, assign to each node sequentially */
    iTreeviewIndx = 1
'/* type lib id for method, ie. function or property get/put */
    iMemberID = 0
    
    For iMemberIndx = 1 To iNbrMembers
        
        Set mi = ii.Members.Item(iMemberIndx)
        iMemberID = iMemberID + 1
        
        If Not ignoreName(mi.Name) Then
            
        '/* method name, method type and return type */
            tvwClasses.Nodes.Add 1, tvwChild, , mi.Name & " - " & _
            getInvokeKindsName(mi.InvokeKind) & _
                " (" & getVTTypeName(mi.ReturnType) & ")"
            
            iTreeviewIndx = iTreeviewIndx + 1
            
        '/* save member id - see InvokeHook logic */
            tvwClasses.Nodes.Item(iTreeviewIndx).Tag = iMemberID
            
            iNbrParms = mi.Parameters.Count
            
            iSaveIndx = iTreeviewIndx
            For iParameterIndx = 1 To iNbrParms
                
            '/* parameter name and type as child node of method */
                tvwClasses.Nodes.Add iSaveIndx, tvwChild, , _
                    mi.Parameters.Item(iParameterIndx).Name & _
                    " (" & getVTTypeName(mi.Parameters.Item _
                    (iParameterIndx).VarTypeInfo) & ")"
                
                iTreeviewIndx = iTreeviewIndx + 1
                
            '/* save parameter type - see InvokeHook logic */
                tvwClasses.Nodes.Item(iTreeviewIndx).Tag = _
                    mi.Parameters(iParameterIndx).VarTypeInfo
                
            Next iParameterIndx
            
        End If
        
    Next iMemberIndx
    
    tvwClasses.Nodes(1).Expanded = True
    
loadTreeviewWithClassInfo_exit:
    Set mi = Nothing
    Set ii = Nothing
    Set ti = Nothing
    Set tli = Nothing
    Set obj = Nothing
    
'/* return */
    loadTreeviewWithClassInfo = sRetInfo
    Exit Function
    
    
loadTreeviewWithClassInfo_error:
    MsgBox Err.Number & " : " & Err.Description & _
           " (loadTreeviewWithClassInfo)"
    Resume loadTreeviewWithClassInfo_exit
    
End Function

Terms of Service | Privacy Statement | Copyright © 2024 UBM Tech, All rights reserved.