Results 1 to 35 of 35

Thread: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

  1. #1

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Resolved [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Ok, I think this one is possible too, but I'm not sure how to get there.

    I'm just talking about VB6 code objects (Classes, Forms, UCs, PropPages, & DataReports).
    And I'm only talking about Public methods.

    I'm staring at some code by Wqweto seen here. That shows how to use IDispatch to go from a method's name to its Dispatch_identifier. However, it doesn't show us how to get from there to the vTable entry.

    Any tips on how to make this step would be greatly appreciated.

    ------------

    Another idea I've got is to just get a complete list of Public methods of the object, in vTable order. From there, it'd be pretty easy. Maybe a function something like the following:

    Code:
    
    Option Explicit
    Private Declare Function CLSIDFromString Lib "ole32" (ByVal lpsz As Any, pclsid As Any) As Long
    Private Declare Function vbaCheckType Lib "msvbvm60" Alias "__vbaCheckType" (ByVal pObj As Any, ByRef pIID As Any) As Boolean
    
    
    Public Function List_Of_Public_Vb6_Com_Methods(o As Object) As String()
        If Not ObjectIsVb6ComCodeModule(o) Then
            List_Of_Public_Vb6_Com_Methods = Split(vbNullString) ' 0 to -1 array.
            Exit Function
        End If
    
    
        ' Somehow call IDispatch::GetIDsOfNames and get the method list.
        ' And hopefully in vTable order.
        ' ??????????????
    
    
    End Function
    
    
    Private Function ObjectIsVb6ComCodeModule(o As IUnknown) As Boolean
        Const AreYouABasicInstance As String = "{0B6C9465-D082-11CF-8B4F-00A0C90F2704}"
        Dim aGUID(3&) As Long
        CLSIDFromString StrPtr(AreYouABasicInstance), aGUID(0&)
        ObjectIsVb6ComCodeModule = vbaCheckType(o, aGUID(0&))
    End Function
    
    Get/Let/Set methods (including Public variables) are a bit of a problem, but I don't really care about those. Maybe they can just be listed twice, without specifying whether they're Get or Let/Set.

    Again, any tips on how to do this would be greatly appreciated.

    ------------

    I'm trying my best to not be a "cargo culter". I'm just not sure where to get started with this, but I'll be searching while I'm waiting on tips.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  2. #2

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Dang, I thought LaVolpe had done it in this thread.

    But he closed the thread with the following:

    Believe I'm going to abandon this train of logic/thought ... Maybe I'll post what I've got (working example) and let others continue down that path if they choose.
    But he didn't post it. Boo.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  3. #3

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Hmmm, I'm poking around at the tObjectInfo and tObject structures, but I'm not making any progress.

    In tObjectInfo, there's an item named aProcTable (aka, aMethodTable). In tObject, there's an item named aProcNamesArray (aka, aMethodNameTable). I've peeked at both of these, and I can't make heads-or-tails of any of it.

    Here's code I'm using to peek at these things:

    Code:
    
    Option Explicit
    '
    Private Type tObjectInfo
        Flag1 As Integer       ' 0x00
        ObjectIndex As Integer ' 0x02
        aObjectTable As Long   ' 0x04
        Null1 As Long          ' 0x08
        aSmallRecord   As Long ' 0x0C (aObjectDescriptor) when it is a module this value is -1 [better name?]
        Const1 As Long         ' 0x10
        Null2 As Long          ' 0x14
        aObject As Long        ' 0x18 (aObjectHeader)
        RunTimeLoaded  As Long ' 0x1C (aObjectData)
        NumberOfProcs  As Long ' 0x20 (iMethodCount, maybe only Integer)
        aProcTable As Long     ' 0x24 (aMethodTable) Pointer to an array of method pointers
        iConstantsCount As Integer '0x28 (40d) Number of Constants
        iMaxConstants   As Integer '0x2A (42d) Maximum Constants to allocate.
        Flag5 As Long          ' 0x2C
        Flag6 As Integer       ' 0x30
        Flag7 As Integer       ' 0x32
        aConstantPool As Long  ' 0x34 (aConstantTable)
                               ' 0x38 <-- Structure Size
                               'the rest is optional items[OptionalObjectInfo]
        '
        dwObjectGuiGuids As Long        ' 0x38 / 0x0 Number of ObjectGUI GUIDs (2 for Designer)
        lpObjectCLSID As Long           ' 0x3C / 0x4 Pointer to object CLSID
        dwNull As Long                  ' 0x40 / 0x8
        lpGuidObjectGUITable As Long    ' 0x44 / 0xC Pointer to pointers of guidObjectGUI
        dwObjectDefaultIIDCount As Long ' 0x48 / 0x10 Number of DefaultIIDs
        lpObjectEventsIIDTable As Long  ' 0x4C / 0x14 Pointer to pointers of EventsIID
        dwObjectEventsIIDCount As Long  ' 0x50 / 0x18 Number of EventsIID
        lpObjectDefaultIIDTable As Long ' 0x54 / 0x1C Pointer to pointers of DefaultIID
        dwControlCount As Long          ' 0x58 / 0x20 dwControlCount Number of Controls in array below.
        lpControls As Long              ' 0x5C / 0x24 lpControls Pointer to Controls Array.
        wMethodLinkCount As Integer     ' 0x60 / 0x28 wMethodLinkCount Number of Method Links
        wPCodeCount As Integer          ' 0x62 / 0x2A wPCodeCount Number of P-Codes used by this Object.
        bWInitializeEvent As Integer    ' 0x64 / 0x2C bWInitializeEvent Offset to Initialize Event from Event Table.
        bWTerminateEvent As Integer     ' 0x66 / 0x2E bWTerminateEvent Offset to Terminate Event in Event Table.
        lpMethodLinkTable As Long       ' 0x68 / 0x30 lpMethodLinkTable Pointer to pointers of MethodLink
        lpBasicClassObject As Long      ' 0x6C / 0x34 lpBasicClassObject Pointer to in-memory Class Objects.
        dwNull3 As Long                 ' 0x70 / 0x38 dwNull3 Unused.
        lpIdeData As Long               ' 0x74 / 0x3C lpIdeData Only valid in IDE.
                                        ' 0x78 / 0x40 <-- Structure Size
    End Type
    
    
    Private Type tObject
        aObjectInfo As Long         ' 0x00
        Const1 As Long              ' 0x04
        aPublicBytes As Long        ' 0x08 (08d) Pointer to Public Variable Size integers
        aStaticBytes As Long        ' 0x0C (12d) Pointer to Static Variables Struct
        aModulePublic As Long       ' 0x10 (16d) Memory Pointer to Public Variables
        aModuleStatic As Long       ' 0x14 (20d) Pointer to Static Variables
        aObjectName As Long         ' 0x18  NTS (aNTSObjectName)
        ProcCount As Long           ' 0x1C events, funcs, subs (lMethodCount, maybe only Integer)
        aProcNamesArray As Long     ' 0x20 when non-zero (aMethodNameTable) Pointer to an array of function addresses
        oStaticVars As Long         ' 0x24 (36d) Offset to Static Vars from aModuleStatic
        ObjectType As Long          ' 0x28
        Null3 As Long               ' 0x2C
                                    ' 0x30  <-- Structure Size
    End Type
    
    Private Declare Function GetMem4 Lib "msvbvm60" (ByRef Source As Any, ByRef Dest As Any) As Long
    Private Declare Function GetMem2 Lib "msvbvm60" (ByRef Source As Any, ByRef Dest As Any) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (ByRef Destination As Any, ByRef Source As Any, ByVal Length As Long)
    
    Public Sub TestProc()
        '
    End Sub
    
    Private Sub Form_Load()
        Dim pVtable         As Long:        GetMem4 ByVal ObjPtr(Me), pVtable
        Dim ptObjectInfo    As Long:        GetMem4 ByVal pVtable - 4&, ptObjectInfo
        Dim uObjectInfo As tObjectInfo:     CopyMemory uObjectInfo, ByVal ptObjectInfo, LenB(uObjectInfo)
        Dim uObject As tObject:             CopyMemory uObject, ByVal uObjectInfo.aObject, LenB(uObject)
    
    
    
    
        '
        ' Report certain values:
        DebugPrint "Test1: " & CStr(uObjectInfo.NumberOfProcs)
        DebugPrint "Test2: " & CStr(uObject.ProcCount)
    
    
    
        DebugPrint "aProcTable     : " & CStr(uObjectInfo.aProcTable)
        DebugPrint "aProcNamesArray: " & CStr(uObject.aProcNamesArray)
    
    
        Dim bb(999) As Byte
        'CopyMemory bb(0), ByVal uObjectInfo.aProcTable, 1000
        CopyMemory bb(0), ByVal uObject.aProcNamesArray, 1000
    
        Dim i As Long
        For i = LBound(bb) To UBound(bb)
            DebugPrint bb(i) & "  " & Chr(bb(i))
        Next
    
    
        Unload Me
    End Sub
    
    
    
    
        'Dim s As String
        's = Space$(500)
        'CopyMemory ByVal StrPtr(s), ByVal uObjectinfo.aProcTable, LenB(s)
        'CopyMemory ByVal StrPtr(s), ByVal uObject.aProcNamesArray, LenB(s)
    
    
        'Dim i As Long
        'For i = 1 To Len(s)
        '    DebugPrint "s: " & AscW(Mid$(s, i, 1)) & "  " & Mid$(s, i, 1)
        'Next
    
    
    I've tried snooping as both Bytes and Unicode characters, but nothing seems to make sense.

    Also, I'm using my persistent Debug window, so you'll have to change the "DebugPrint" to something else to see the results if you wish to test. But they're just nonsense in all cases.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  4. #4
    PowerPoster
    Join Date
    Feb 2015
    Posts
    2,687

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Code:
    Option Explicit
    Option Base 0
    
    Public Enum PTR
        [_]
    End Enum
    
    Private Declare Function GetMem1 Lib "msvbvm60" ( _
                             ByRef Source As Any, _
                             ByRef Dest As Any) As Long
    Private Declare Function GetMem4 Lib "msvbvm60" ( _
                             ByRef Source As Any, _
                             ByRef Dest As Any) As Long
    Private Declare Function GetMemPtr Lib "msvbvm60" Alias "GetMem4" ( _
                             ByRef Source As Any, _
                             ByRef Dest As Any) As Long
    Private Declare Function GetMem2 Lib "msvbvm60" ( _
                             ByRef Source As Any, _
                             ByRef Dest As Any) As Long
    Private Declare Function lstrlenA Lib "kernel32" ( _
                             ByRef lpString As Any) As Long
    Private Declare Function SysAllocStringByteLen Lib "oleaut32" ( _
                             ByRef psz As Any, _
                             ByVal lSize As Long) As String
    
    ' // Get list of VB6 object methods
    Public Property Get ListOfMethods( _
                        ByVal cObj As Object) As String()
        Dim sRet()      As String
        Dim lIndex      As Long
        Dim lCount      As Long
        Dim pObjInfo    As PTR
        Dim pPubDesc    As PTR
        Dim pPrivDesc   As PTR
        Dim pMembers    As PTR
        Dim pMethDesc   As PTR
        Dim pVTbl       As PTR
        Dim lMethods    As Long
        Dim pNames      As PTR
        Dim pName       As PTR
        Dim lMethOffset As Long
        Dim lPropCount  As Long
        Dim lFlags      As Long
        
        GetMemPtr ByVal ObjPtr(cObj), pVTbl
        GetMemPtr ByVal pVTbl - 4, pObjInfo
        GetMemPtr ByVal pObjInfo + &H18, pPubDesc
        GetMemPtr ByVal pObjInfo + &HC, pPrivDesc
        GetMemPtr ByVal pPubDesc + &H20, pNames
        
        If pPrivDesc = 0 Then
            Exit Property
        End If
        
        GetMemPtr ByVal pPrivDesc + &H18, pMembers
        GetMem2 ByVal pPubDesc + &H1C, lMethods
        
        If lMethods = 0 Then
            Exit Property
        End If
    
        For lIndex = 0 To lMethods - 1
            
            GetMemPtr ByVal pMembers, pMethDesc
    
            If pMethDesc Then
                
                GetMem2 ByVal pMethDesc + 2, lMethOffset
                
                If lMethOffset And 1 Then
                    
                    lMethOffset = lMethOffset And -2
                    
                    GetMemPtr ByVal pNames + lIndex * Len(pName), pName
                    
                    If lCount Then
                        If lCount > UBound(sRet) Then
                            ReDim Preserve sRet(lCount + 10)
                        End If
                    Else
                        ReDim sRet(9)
                    End If
                    
                    sRet(lCount) = SysAllocStringByteLen(ByVal pName, lstrlenA(ByVal pName))
                    
                    lCount = lCount + 1
                    
                End If
    
            End If
            
            pMembers = pMembers + 4
            
        Next
        
        GetMem2 ByVal pPrivDesc + &H10, lPropCount
        GetMemPtr ByVal pPrivDesc + &H20, pMembers
        
        For lIndex = 0 To lPropCount - 1
            
            GetMemPtr ByVal pMembers, pMethDesc
            
            If pMethDesc Then
                
                GetMem2 ByVal pMethDesc + &H10, lFlags
                
                If lFlags And 2 Then
                    
                    GetMemPtr ByVal pMethDesc, pName
                    GetMem2 ByVal pMethDesc + &H12, lMethOffset
                    
                    If lCount Then
                        If lCount > UBound(sRet) Then
                            ReDim Preserve sRet(lCount + 10)
                        End If
                    Else
                        ReDim sRet(9)
                    End If
                    
                    sRet(lCount) = SysAllocStringByteLen(ByVal pName, lstrlenA(ByVal pName))
                    
                    lCount = lCount + 1
                    
                End If
                
            End If
            
            pMembers = pMembers + 4
    
        Next
        
        If lCount Then
            ReDim Preserve sRet(lCount - 1)
        End If
        
        ListOfMethods = sRet
        
    End Property

  5. #5

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Trick, that's crazy cool.

    I tested both in IDE and compiled, and it works flawlessly.

    THANK YOU!!!

    (Now I've got to study it and see if I can understand it.)
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  6. #6

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Hi Trick,

    Ok, I'm slowly getting my head around this.

    There are a couple of bugs in the "Properties" loop though (the second loop). The "Methods/Procedures" loop seems to be working fine.

    1. It's picking up both Public and Private Properties.
    2. If there is more than one Property (module level variable), it's reporting the same name (the first one) for all of them.

    -----------

    I could possibly fix the second one. But I'm not sure how to fix the first one. I tried doing it the same way as the Methods/Procedures (GetMem2 ByVal pMethDesc + 2, lMethOffset: If lMethOffset And 1 Then ...) but that didn't work. So I just don't know where the Public/Private flag is for these Properties.

    I'll work on fixing the first one (the names of the Properties).

    Again, a HUGE thanks for this.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  7. #7

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Ahhh, the same fix fixed both bugs:

    In Trick's second loop, just after the For lIndex = 0 To lPropCount - 1, the following line:

    Code:
    
            GetMemPtr ByVal pMembers, pMethDesc
    
    ... needs to be changed to ...

    Code:
    
            GetMem4 ByVal pMembers + lIndex * 4&, pMethDesc
    
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  8. #8
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    pMethDesc + &H12, lMethOffset do you have a description of this field vtable offset of the property ?

    +&h14 i is the data offset for storage (ie Objptr()+[pMethDesc + &h14]) i believe

    also did you have a breakdown of the flags meaning for following:

    pMethDesc + &H10, lFlags

    I have seen the pMethDesc + 2, lMethOffset bit 1 flag set but not sure of its meaning either, its weird they stuffed a bit flag in there like that

  9. #9

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Quote Originally Posted by dz32 View Post
    pMethDesc + &H12, lMethOffset do you have a description of this field vtable offset of the property ?

    +&h14 i is the data offset for storage (ie Objptr()+[pMethDesc + &h14]) i believe

    also did you have a breakdown of the flags meaning for following:

    pMethDesc + &H10, lFlags

    I have seen the pMethDesc + 2, lMethOffset bit 1 flag set but not sure of its meaning either, its weird they stuffed a bit flag in there like that
    Hold on. Give me a few minutes. I'm reworking the whole thing with as many comments as I can figure out.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  10. #10

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Ok, here's my current effort to understand this thing:

    Code:
    
    Option Explicit
    
    Private Declare Function GetMem1 Lib "msvbvm60" (ByRef Source As Any, ByRef Dest As Any) As Long
    Private Declare Function GetMem4 Lib "msvbvm60" (ByRef Source As Any, ByRef Dest As Any) As Long
    Private Declare Function GetMem2 Lib "msvbvm60" (ByRef Source As Any, ByRef Dest As Any) As Long
    Private Declare Function lstrlenA Lib "kernel32" (ByRef lpString As Any) As Long
    Private Declare Function SysAllocStringByteLen Lib "oleaut32" (ByRef psz As Any, ByVal lSize As Long) As String
    Private Declare Function CLSIDFromString Lib "ole32" (ByVal lpsz As Any, pclsid As Any) As Long
    Private Declare Function vbaCheckType Lib "msvbvm60" Alias "__vbaCheckType" (ByVal pObj As Any, ByRef pIID As Any) As Boolean
    
    Private Sub Form_Load()
        Dim sa() As String
        sa = ListOfPublicVb6ComMembers(Me)
        Dim i As Long
        For i = LBound(sa) To UBound(sa)
            MsgBox sa(i)
        Next
    
    
        Unload Me
    End Sub
    
    Public Function ListOfPublicVb6ComMembers(ByVal o As Object) As String()
        ' These should be returned in vTable order.
        ' So, after the offset for IUnknown & IDispatch as well as the intrinsic members,
        ' This can tell us a vTable offset for these members.
        ' It's zero-based so don't forget that when searching the returned string array.
        '
        ListOfPublicVb6ComMembers = Split(vbNullString)                             ' Just a default return.
        If Not ObjectIsVb6ComCodeModule(o) Then Exit Function                       ' Make sure we're dealing with a VB6 COM-code object.
        '
        Dim pVTbl       As Long:    GetMem4 ByVal ObjPtr(o), pVTbl                  ' Pointer to vTable.
        Dim pObjInfo    As Long:    GetMem4 ByVal pVTbl - 4&, pObjInfo              ' Pointer to tObjectInfo structure.
        Dim pPubDesc    As Long:    GetMem4 ByVal pObjInfo + &H18&, pPubDesc        ' tObjectInfo.aObject which points to tObject structure.
        Dim pPrivDesc   As Long:    GetMem4 ByVal pObjInfo + &HC&, pPrivDesc        ' tObjectInfo.lpPrivateObject which points to tPrivateObj structure.
        '
        If pPrivDesc = 0& Then Exit Function                                        ' Just a double-check.
        '
        Dim sRet()      As String:  sRet = Split(vbNullString)                      ' Start with 0 to -1 array.
        Dim lIndex      As Long
        Dim lCount      As Long
        Dim pName       As Long
        '
        ' Gather the Public Variables at the top of the module.
        Dim lFlags      As Long
        Dim pPropDesc   As Long
        Dim lPropsCnt   As Long:    GetMem2 ByVal pPrivDesc + &H10&, lPropsCnt      ' tPrivateObj.cntPublicVars value.
        Dim pPropsPtr   As Long:    GetMem4 ByVal pPrivDesc + &H20&, pPropsPtr      ' tPrivateObj.lpPublicVars which points to array of pointers to structure with property info (tPropInfo).
        '
        For lIndex = 0& To lPropsCnt - 1&
            GetMem4 ByVal pPropsPtr + lIndex * 4&, pPropDesc                        ' Get tPropInfo for property.
            If pPropDesc Then                                                       ' Zero if not "Public".
                GetMem2 ByVal pPropDesc + &H10&, lFlags                             ' tPropInfo.lFlags.
                If lFlags And 2& Then                                               ' Not sure why this is tested (maybe double-check for "Public")???
                    GetMem4 ByVal pPropDesc, pName                                  ' tPropInfo.pName, pointer to property's name.
                    If (lCount + 1&) > UBound(sRet) Then ReDim Preserve sRet(lCount + 100&)
                    ' Return TWO entries so we can keep the vTable count correct.
                    sRet(lCount) = "Get var " & SysAllocStringByteLen(ByVal pName, lstrlenA(ByVal pName))
                    lCount = lCount + 1&
                    sRet(lCount) = "Let/Set var " & SysAllocStringByteLen(ByVal pName, lstrlenA(ByVal pName))
                    lCount = lCount + 1&
                End If
            End If
        Next
        '
        ' Gather the Public Properties within the module.
        Dim lMethOffset As Long
        Dim pMethDesc   As Long
        Dim lMethodsCnt As Long:    GetMem2 ByVal pPubDesc + &H1C&, lMethodsCnt     ' tObject.ProcCount value.
        Dim pNames      As Long:    GetMem4 ByVal pPubDesc + &H20&, pNames          ' tObject.aProcNamesArray which points to an array of name pointers.
        Dim pMethodsPtr As Long:    GetMem4 ByVal pPrivDesc + &H18&, pMethodsPtr    ' tPrivateObj.lpFuncTypeInfo which points to an array of pointers.
        '
        For lIndex = 0& To lMethodsCnt - 1&
            GetMem4 ByVal pMethodsPtr + lIndex * 4&, pMethDesc                      ' From the array, getting a pointer to a method structure (tMethInfo).
            If pMethDesc Then                                                       ' Not sure if this ever returns zero, maybe for "Private" methods?
                GetMem2 ByVal pMethDesc + 2&, lMethOffset                           ' A flag out of tMethInfo structure.
                If lMethOffset And 1& Then                                          ' "Public" bit from flag.
                    GetMem4 ByVal pNames + lIndex * 4&, pName                       ' Dig pointer to method name from array of name pointers.
                    If lCount > UBound(sRet) Then ReDim Preserve sRet(lCount + 100&)
                    sRet(lCount) = SysAllocStringByteLen(ByVal pName, lstrlenA(ByVal pName))
                    lCount = lCount + 1&                                            ' This time, only count once, as Get & Let/Set appear separately for methods.
                End If
            End If
        Next
        '
        ' Return what we found, or 0 to -1 array.
        If lCount Then
            ReDim Preserve sRet(lCount - 1&)
            ListOfPublicVb6ComMembers = sRet
        End If
    End Function
    
    Public Function ObjectIsVb6ComCodeModule(o As IUnknown) As Boolean
        Const AreYouABasicInstance As String = "{0B6C9465-D082-11CF-8B4F-00A0C90F2704}"
        Dim aGUID(3&) As Long
        CLSIDFromString StrPtr(AreYouABasicInstance), aGUID(0&)
        ObjectIsVb6ComCodeModule = vbaCheckType(o, aGUID(0&))
    End Function
    
    What'd I do:

    • Renamed the function.
    • Fixed the bug in the "properties" loop.
    • Reversed the "methods" loop and the "properties" loop so they'd return in vTable order.
    • Moved the Dim declarations around to be closer to where they're used.
    • Made a separate set of variables for the "properties" loop and the "methods" loop.
    • Documented as much as I could figure out.
    • Just made longer lines. I've got a very wide monitor, so I like the long lines. I also "pretend" I've got declare-and-assign (like C/C++) and put it all on the same line.
    • Added TWO entries for the properties (i.e., Public variables). I also prepended "Get var " and "Let/Set var " to these.

    What I still don't understand:

    • I've got no documentation for the tPropInfo structure. It's clearly a structure array for the properties. In fact, I just made up that name. pName and lFlags are coming out of it.
    • I've got no documentation for the tPropInfo.lFlags or its bits. In fact, it seems to run the same regardless of whether that flag is checked or not.
    • I've got no documentation for the tMethInfo structure. Again, it's clearly a structure array for the methods. Again, I just made up the structure name. lMethOffset is coming out of it, which is really some bit flags.
    • I've got no documentation for the tMethInfo.lMethOffset flags or its bits.

    Maybe The Trick will notice this and provide us some documentation for these structures. I'm glad it works though.
    Last edited by Elroy; Oct 25th, 2022 at 05:35 PM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  11. #11
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    the following is my current understanding of these structs. dont have offsets added into my defs but vbdec will show them in its struct dumps

    Code:
    Private Type tPrivateObj
        nul1 As Long
        lpParentLink As Long
        unk1 As Long
        nul2 As Long
        cntPublicVars As Integer
        cntEvents As Integer
        nul3 As Long
        lpFuncTypeInfo As Long  'array of pubFuncTypeDesc pointers, nulls for private funcs with Object->ProcCount members
        nul4 As Long
        lpPublicVars As Long  'array of pubVarTypeDesc pointers  with cntPublicVars members
        lpEventsTypeInfo As Long 'array of  pubEventTypeDesc pointers with cntEvents members
        lpNull As Long
        nul5 As Long
        nul6 As Long
        nul7 As Long
        unk3 As Long
        unk4 As Long
    End Type
    
    
    Private Type pubEventTypeDesc
        argSize As Byte
        isFunc As Byte
        constFFFF As Long
        nul1 As Long
        nul2 As Integer
        memberID As Long
        lpAryArgNames As Long   'last array entry null
        lpFuncDesc As Long
        nul3 As Long
        helpID As Long
        unk1 As Byte 'always 1e for hResult?
    End Type
    
    Private Type pubFuncTypeDesc
        argSize As Byte
        flags As Byte
        vOff As Integer
        constFFFF As Integer
        nul1 As Integer
        optionalVals As Long
        memberID As Long
        lpAryArgNames As Long  
        lpFuncDesc As Long
        nul3 As Long
        helpID As Long
        unk1 As Byte 'always 1e ?
    End Type
    
    Private Type pubVarTypeDesc
        lpName As Long
        nul1 As Long
        nul2 As Long
        index As Integer
        unk1 As Byte
        unk2 As Byte
        unk3 As Integer
        unk4 As Integer
        varOffset As Long  'from objPtr for data store
    End Type
    Last edited by dz32; Oct 25th, 2022 at 05:28 PM.

  12. #12

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Quote Originally Posted by dz32 View Post
    the following is my current understanding of these structs.
    Thanks. I like having that documentation.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  13. #13

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: VB6 COM/Code Object Method Name ---> vTable Entry Number

    Using the above (code in post #10), the following can be used to determine the vTable entry. Please be sure to read the comments:

    Code:
    
    Public Function VtableEntryForPublicMethod(ByVal o As Object, ByVal sMethodName As String) As Long
        ' Returns the 1-based vTable entry offset for sMethodName.
        ' The IUnknown, IDispatch, and intrinsic vTable entries are NOT accounted for, and must be added.
        ' If a Get or Let/Set method is searched, the first one found will be returned (order in source code).
        ' There is no provision for returning "Property" (Public variables) vTable entries,
        ' but they will be correctly counted in the returned offset.
        '
        ' If it can't be found, ZERO is returned.
        '
        Dim sa() As String
        sa = ListOfPublicVb6ComMembers(o)
        sMethodName = UCase$(sMethodName)       ' Make sure we're case-insensitive, as VB6 is.
        Dim i As Long
        For i = LBound(sa) To UBound(sa)
            If UCase$(sa(i)) = sMethodName Then
                VtableEntryForPublicMethod = i + 1&
                Exit Function
            End If
        Next
        ' If we fall out, it's not found so return 0.
    End Function
    
    
    So, unless there's something wrong that I haven't found, this one is resolved.

    Just as an FYI, I've tested both IDE running and machine compiled, and it seems to all work fine.
    Last edited by Elroy; Oct 25th, 2022 at 05:41 PM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  14. #14
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    I would use the pubFuncTypeDesc.voff value over a self calculated value for vtable offset
    This is what trick had and -2 because they set bit 1 of that field as a flag for some reason

    All public vars will generate a get/let pair, and some will generate a get/let/set depending on variable type
    Variant and object data types should have 3 entries per. There is a way to check the type of the var that’s part of tomorrows article.
    Last edited by dz32; Oct 25th, 2022 at 06:18 PM.

  15. #15

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Quote Originally Posted by dz32 View Post
    I would use the pubFuncTypeDesc.voff value over a self calculated value for vtable offset
    This is what trick had and -2 because they set bit 1 of that field as a flag for some reason

    All public vars will generate a get/let pair, and some will generate a get/let/set depending on variable type
    Variant and object data types should have 3 entries per. There is a way to check the type of the var that’s part of tomorrows article.
    Oh WOW, I didn't think about there actually being a stored value for the offset. I'll definitely look into it.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  16. #16
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    what I have as pubVarTypeDesc.unk4 trick correctly noticed is the vtable offset for the first property get of that particular public variable.

    I do not see anything in the structure that lists explicitly if it has an additional set property with it. (although you can figure it out looking at the variable type.)

    one of my dumps for the following:

    Code:
    Public a As Long
    Public myPublicVar As Scripting.FileSystemObject
    Property Let myManualProp(d As Date, i As Long)
    
    Public VarTypes: 
    	VA       Off   Name    = Value
    	40214C   000   lpName = 402394 -> Public a As Long (reconstructed prototype)
    	402150   004   nul1 = 0
    	402154   008   nul2 = 0
    	402158   00C   index = 0
    	40215A   00E   unk1 = 3
    	40215B   00F   unk2 = 40
    	40215C   010   unk3 = 2
    	40215E   012   unk4 = 1C       <-- first vtable offset for this property get
    	402160   014   varOffset = 3C
    
    	VA       Off   Name    = Value
    	402168   000   lpName = 402398 -> Public myPublicVar As IFileSystem3  (reconstructed prototype)
    	40216C   004   nul1 = 0
    	402170   008   nul2 = 0
    	402174   00C   index = 1
    	402176   00E   unk1 = 3
    	402177   00F   unk2 = 40
    	402178   010   unk3 = 2
    	40217A   012   unk4 = 24            <-- first vtable offset for this property get (1c/20 taken by get/let Public a As Long)
    	40217C   014   varOffset = 40
    
    Public Funcs:
      Public Property Let myManualProp(d As Date, i As Long)  (reconstructed prototype)
    	VA       Off   Name    = Value
    	40225C   000   argSize = A (2 args)
    	40225D   001   flags = 0
    	40225E   002   vOff = 31                <-- vtable offset +1 for this property (24/28/2c taken by  get/let/set myPublicVar)
    	402260   004   constFFFF = FFFF
    	402262   006   nul1 = 0
    	402264   008   optionalVals = 0
    	402268   00C   memberID = 68030001
    	40226C   010   lpAryArgNames = 4020FC
    	402270   014   lpFuncDesc = 0
    	402274   018   nul3 = 0
    	402278   01C   helpID = 0
    	40227C   020   unk1 = 1E
    	TypeBytes: 2C 28 0
    and the autogenerated native stubs for those get/let/sets where you can see the varOffset in use

    Code:
    .text:0040175C CMYClassMethLnkTable:                   ; DATA XREF: .text:CMYClass_OptInfo_MethLnk↑o
    .text:0040175C                 add     dword ptr [esp+4], 3Ch ; '<'
    .text:00401764                 mov     ecx, offset GetMem4
    .text:00401769                 jmp     ecx
    .text:0040176B ; ---------------------------------------------------------------------------
    .text:0040176B                 add     dword ptr [esp+4], 3Ch ; '<'
    .text:00401773                 mov     ecx, offset PutMem4
    .text:00401778                 jmp     ecx
    .text:0040177A ; ---------------------------------------------------------------------------
    .text:0040177A                 add     dword ptr [esp+4], 40h ; '@'
    .text:00401782                 mov     ecx, offset GetMemObj
    .text:00401787                 jmp     ecx
    .text:00401789 ; ---------------------------------------------------------------------------
    .text:00401789                 add     dword ptr [esp+4], 40h ; '@'
    .text:00401791                 mov     ecx, offset PutMemObj
    .text:00401796                 jmp     ecx
    .text:00401798 ; ---------------------------------------------------------------------------
    .text:00401798                 add     dword ptr [esp+4], 40h ; '@'
    .text:004017A0                 mov     ecx, offset SetMemObj
    .text:004017A5                 jmp     ecx
    and just for complete data visualization

    Code:
    .text:00402370 CMYClass_PrivateObj dd 0                    ; nul1
    .text:00402370                 dd offset CMYClass_ObjInfo; lpParentLink
    .text:00402370                 dd 0FFFFFFFFh           ; unk1
    .text:00402370                 dd 0                    ; nul2
    .text:00402370                 dw 3                    ; cntPublicVars
    .text:00402370                 dw 2                    ; cntEvents
    .text:00402370                 dd 0                    ; nul3
    .text:00402370                 dd offset CMYClass_FuncDesc; lpFuncTypeInfo
    .text:00402370                 dd 0                    ; nul4
    .text:00402370                 dd offset CMYClass_Priv_PubVars; lpPublicVars
    .text:00402370                 dd offset CMYClass_Priv_EvtTypInf; lpEventsTypeInfo
    .text:00402370                 dd offset nullVal_3     ; lpNull
    .text:00402370                 dd 0                    ; nul5
    .text:00402370                 dd 0                    ; nul6
    .text:00402370                 dd 0                    ; nul7
    .text:00402370                 dd 54h                  ; unk3
    .text:00402370                 dd 104h                 ; unk4
    
    .text:00402104 CMYClass_Priv_PubVars dd offset CMYClass_PubVarTypDesc_0
    .text:00402108                       dd offset CMYClass_PubVarTypDesc_1
    
    .text:004021A8 CMYClass_PubVarTypDesc_0 dd offset aA            ; lpName
    .text:004021A8                 dd 0                    ; nul1 ; "a"
    .text:004021A8                 dd 0                    ; nul2
    .text:004021A8                 dw 0                    ; index
    .text:004021A8                 db 3                    ; unk1
    .text:004021A8                 db 40h                  ; unk2
    .text:004021A8                 dw 2                    ; unk3
    .text:004021A8                 dw 1Ch                  ; vOff
    .text:004021A8                 dd 3Ch                  ; varOffset
    .text:004021C0                 dw 8
    .text:004021C2                 db    0
    .text:004021C3                 db    0
    
    .text:00402168 CMYClass_PubVarTypDesc_1 dd offset aMypublicvar  ; lpName
    .text:00402168                 dd 0                    ; nul1 ; "myPublicVar"
    .text:00402168                 dd 0                    ; nul2
    .text:00402168                 dw 1                    ; index
    .text:00402168                 db 3                    ; unk1
    .text:00402168                 db 40h                  ; unk2
    .text:00402168                 dw 2                    ; unk3
    .text:00402168                 dw 24h                  ; vOff
    .text:00402168                 dd 40h                  ; varOffset
    .text:00402180                 dd 1Dh
    .text:00402184                 dd offset off_4023A4
    all of those structures are automatically created and named from the IDC script generated by the IDC Structs node in the vbdec treeview
    Last edited by dz32; Oct 25th, 2022 at 07:24 PM.

  17. #17
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Also you should be able to extract the entire structure from memory with a copy memory call if you rather work with names fields

  18. #18

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Ok, this is very nice. vOff (or lMethOffset as Trick calls it) is a bit strange.

    The first two (low order) bits are some kind flags. The first one is a Public=1, Private/Friend=0 flag. I don't know what the second bit is. It's not Private vs Friend.

    So, if we just go vOff = vOff \ 4 we then have a true zero-based offset (count) into the vTable.
    If we further go vOff = vOff * 4 we then have a true "offset" into the vTable address for this method.

    Or, since vTable offsets are always multiples of 4, a simple vOff = vOff And &FFFFFFFC then we've got the vTable offset address.
    Last edited by Elroy; Oct 25th, 2022 at 09:03 PM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  19. #19

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    So, we can do the following and go straight from a method name to a vTable address offset (already multiplied by 4). Just need to add the vTable address to it and it takes us straight to the method's address in the object. And it searches Public, Private, & Friend methods. This is better than I'd hoped for.

    Code:
    
    Public Function VtableOffsetForVb6ComMethod(ByVal o As Object, ByVal sMethodName As String) As Long
        ' Searches Public, Friend, & Private methods.
        ' Does NOT search properties (i.e., Public variables).
        ' Returns an OFFSET address ready to be added to the vTable address.
        ' If a Get or Let/Set method is searched, the first one found will be returned (order in source code).
        '
        ' If it can't be found, ZERO is returned.
        '
        If Not ObjectIsVb6ComCodeModule(o) Then Exit Function                       ' Make sure we're dealing with a VB6 COM-code object.
        sMethodName = UCase$(sMethodName)
        '
        Dim pVTbl       As Long:    GetMem4 ByVal ObjPtr(o), pVTbl                  ' Pointer to vTable.
        Dim pObjInfo    As Long:    GetMem4 ByVal pVTbl - 4&, pObjInfo              ' Pointer to tObjectInfo structure.
        Dim pPubDesc    As Long:    GetMem4 ByVal pObjInfo + &H18&, pPubDesc        ' tObjectInfo.aObject which points to tObject structure.
        Dim pPrivDesc   As Long:    GetMem4 ByVal pObjInfo + &HC&, pPrivDesc        ' tObjectInfo.lpPrivateObject which points to tPrivateObj structure.
        '
        If pPrivDesc = 0& Then Exit Function                                        ' Just a double-check.
        '
        Dim lIndex      As Long
        Dim pName       As Long
        '
        ' Search the procedures within the module.
        Dim pMethDesc   As Long
        Dim lMethodsCnt As Long:    GetMem2 ByVal pPubDesc + &H1C&, lMethodsCnt     ' tObject.ProcCount value.
        Dim pNames      As Long:    GetMem4 ByVal pPubDesc + &H20&, pNames          ' tObject.aProcNamesArray which points to an array of name pointers.
        Dim pMethodsPtr As Long:    GetMem4 ByVal pPrivDesc + &H18&, pMethodsPtr    ' tPrivateObj.lpFuncTypeInfo which points to an array of pointers.
        '
        ' Loop through methods and see if we can find the one we want.
        For lIndex = 0& To lMethodsCnt - 1&
            GetMem4 ByVal pMethodsPtr + lIndex * 4&, pMethDesc                      ' From the array, getting a pointer to a method structure (tMethInfo).
            If pMethDesc Then                                                       ' Not sure if this ever returns zero, maybe for "Private" methods?
                GetMem4 ByVal pNames + lIndex * 4&, pName                           ' Dig pointer to method name from array of name pointers.
                If sMethodName = UCase$(SysAllocStringByteLen(ByVal pName, lstrlenA(ByVal pName))) Then
                    Dim iMethOffset As Integer
                    GetMem2 ByVal pMethDesc + 2&, iMethOffset
                    VtableOffsetForVb6ComMethod = CLng(iMethOffset And &HFFFC)
                    Exit Function
                End If
            End If
        Next
        '
        ' Return zero if not found.
    End Function
    
    
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  20. #20
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Interesting. I haven’t explored these structures in the ide much just from compiled files.

    For compiled files the array of the pubfuncdesc Pointers will have embedded nulls for any private or friend methods.

    It makes sense in the ide there would be more info available and that some flag values may only have meaning within the ide since generated structures would best be reused.

    Why they would superimpose a bit field on the low order bits they technically knew would never be used for the target data since it’s always mod 4 I dunno. That decision probably goes back to vb2 or 3 or something.

    They do a similar thing with the “argsize” field. The first three bits are used to define if the method is a property get/let/set because valid values for the main use of this field are mod 4 as well. Flags can be 0 for subs, 1 for functions and oddly they set the bits 0xfc if the last parameter is a paramarray

    We are dealing with code generated in old times.

    Honestly one of the things I love about playing with this stuff is looking at the engineering of how it was done.
    Last edited by dz32; Oct 29th, 2022 at 11:16 PM.

  21. #21

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    @dz32

    I'm testing both running in IDE and running compiled (machine code). Everything is working both ways.

    ADDED: Actually, I haven't tested that in the last hour or two. I'll check it now.

    ADDED2: Ahh, crud, you're right. It only works on Public methods.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  22. #22
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,156

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Btw, this skips CLSIDFromString call

    Code:
    Public Function ObjectIsVb6ComCodeModule(o As IUnknown) As Boolean
        Dim aGUID(0 To 1) As Currency ' {0B6C9465-D082-11CF-8B4F-00A0C90F2704}
        aGUID(0) = 128347367577987.1845@
        aGUID(1) = 29922525889064.5387@
        ObjectIsVb6ComCodeModule = vbaCheckType(o, aGUID(0))
    End Function
    cheers,
    </wqw>

  23. #23
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Here is the article I mentioned describing some more details on the structures and bit field values. We can actually reconstruct the entire function prototype from the data embedded in these structures. It is part of how the vb idispatch plumbing operates.

    https://decoded.avast.io/davidzimmer...6-executables/

    This is how I spent my week vacation this year lol
    (Along with learning to tig weld aluminum)

  24. #24

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Quote Originally Posted by wqweto View Post
    Btw, this skips CLSIDFromString call

    Code:
    Public Function ObjectIsVb6ComCodeModule(o As IUnknown) As Boolean
        Dim aGUID(0 To 1) As Currency ' {0B6C9465-D082-11CF-8B4F-00A0C90F2704}
        aGUID(0) = 128347367577987.1845@
        aGUID(1) = 29922525889064.5387@
        ObjectIsVb6ComCodeModule = vbaCheckType(o, aGUID(0))
    End Function
    cheers,
    </wqw>
    Ahhh, I like it. I'll swap mine out. Thanks for figuring out those Currency constants. I'm hoping to make a "terse" version when I'm all done with this.

    Quote Originally Posted by dz32 View Post
    Here is the article I mentioned describing some more details on the structures and bit field values. We can actually reconstruct the entire function prototype from the data embedded in these structures. It is part of how the vb idispatch plumbing operates.

    https://decoded.avast.io/davidzimmer...6-executables/

    This is how I spent my week vacation this year lol
    (Along with learning to tig weld aluminum)
    Thanks dz32. I'll definitely read it. It looks like a good article.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  25. #25

  26. #26

  27. #27
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    We’re just a couple inches away from implementing reflection for all vb6 classes and forms now without needing tlbinf
    Last edited by dz32; Oct 26th, 2022 at 12:01 PM.

  28. #28
    PowerPoster
    Join Date
    Feb 2015
    Posts
    2,687

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Quote Originally Posted by dz32 View Post
    They do a similar thing with the “argsize” field. The first three bits are used to define if the method is a property get/let/set because valid values for the main use of this field are mod 4 as well.
    Code:
    MethType = 2 ^ (MethType And &H3)
    then
    Code:
                Select Case data(index).MethType
                Case VbGet:     sItem = "Public Property Get"
                Case VbLet:     sItem = "Public Property Let"
                Case VbSet:     sItem = "Public Property Set"
                Case VbMethod:  sItem = "Public Function"
                Case 255:       sItem = "Public Variable"
                End Select

  29. #29

  30. #30
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Cool thanks

  31. #31

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Trick,

    I think it's absolutely amazing, all the "tricks" you've provided on these forums.

    You've pulled so many rabbits out of your hat that I think you've got a rabbit farm in there.

    You Take Care,
    Elroy
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  32. #32
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,156

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Couple of links explaining object info internals

    https://www.hex-rays.com/products/id...eefiles/vb.idc

    https://github.com/williballenthin/p...vb/__init__.py -- this one contains a lot of other links

    Here is a memory dumping function I use to explore in Immediate Window

    Code:
    '--- mdDesignDump.bas
    Option Explicit
    
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    Private Declare Function IsBadReadPtr Lib "kernel32" (ByVal lp As Long, ByVal ucb As Long) As Long
    
    Public Function DesignDumpMemory(ByVal lPtr As Long, ByVal lSize As Long) As String
        Dim lIdx            As Long
        Dim sHex            As String
        Dim sChar           As String
        Dim lValue          As Long
        Dim aResult()       As String
        
        ReDim aResult(0 To (lSize + 15) \ 16) As String
        For lIdx = 0 To ((lSize + 15) \ 16) * 16
            If lIdx < lSize Then
                If IsBadReadPtr(lPtr, 1) = 0 Then
                    Call CopyMemory(lValue, ByVal lPtr, 1)
                    sHex = sHex & Right$("0" & Hex$(lValue), 2) & " "
                    If lValue >= 32 Then
                        sChar = sChar & Chr$(lValue)
                    Else
                        sChar = sChar & "."
                    End If
                Else
                    sHex = sHex & "?? "
                    sChar = sChar & "."
                End If
            Else
                sHex = sHex & "   "
            End If
            If ((lIdx + 1) Mod 4) = 0 Then
                sHex = sHex & " "
            End If
            If ((lIdx + 1) Mod 16) = 0 Then
                aResult(lIdx \ 16) = Right$("000" & Hex$(lIdx - 15), 4) & " - " & sHex & sChar
                sHex = vbNullString
                sChar = vbNullString
            End If
            lPtr = (lPtr Xor &H80000000) + 1 Xor &H80000000
        Next
        DesignDumpMemory = Join(aResult, vbCrLf)
    End Function
    cheers,
    </wqw>

  33. #33

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Quote Originally Posted by wqweto View Post
    Couple of links explaining object info internals

    https://www.hex-rays.com/products/id...eefiles/vb.idc

    https://github.com/williballenthin/p...vb/__init__.py -- this one contains a lot of other links

    cheers,
    </wqw>
    Thanks for these. When you need this stuff, it's good to have it.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  34. #34
    Frenzied Member
    Join Date
    Jun 2015
    Posts
    1,068

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Starting to look into how implements works. It messes with the vtable and public variables table

    http://sandsprite.com/blogs/index.ph...=517&year=2022

  35. #35

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [RESOLVED] VB6 COM/Code Object Method Name ---> vTable Entry Number

    Quote Originally Posted by dz32 View Post
    Starting to look into how implements works. It messes with the vtable and public variables table

    http://sandsprite.com/blogs/index.ph...=517&year=2022
    Yeah, when I get a chunk of time, I need to look into this. I've just got several other things going on right now, but I'll get to it.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width