Results 1 to 12 of 12

Thread: [VB6/VBA] Collection keys

  1. #1

    Thread Starter
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,154

    [VB6/VBA] Collection keys

    These are x64 and 32-bit implementations of some keys access/enumeration functions for built-in VBA.Collection class as discussed in http://www.vbforums.com/showthread.p...ted-Collection

    The internal VbCollectionHeader and VbCollectionItem structs are declared w/ member offsets both for x64 and 32-bit implementations and the raw pointer access is implemented in bitness agnostic fashion w/ PTR_SIZE const and VbCollectionOffsets enum members e.g. single code Call CopyMemory(lPtr, ByVal lPtr + o_pNextIndexedItem, PTR_SIZE) works correctly both for x64 and 32-bit versions the same.

    The mystery coincidence of matching offset for VbCollectionHeader.pNextIndexedItem and VbCollectionItem.pFirstIndexedItem holds true for x64 versions of the internal structs, so IMO this is very deliberate impl. detail.

    thinBasic Code:
    1. Option Explicit
    2.  
    3. #Const HasPtrSafe = (VBA7 <> 0)
    4. #Const LargeAddressAware = (Win64 = 0 And VBA7 = 0 And VBA6 = 0 And VBA5 = 0)
    5.  
    6. '--- for CopyMemory
    7. #If HasPtrSafe Then
    8.     Private Const NULL_PTR                  As LongPtr = 0
    9. #Else
    10.     Private Const NULL_PTR                  As Long = 0
    11. #End If
    12. #If Win64 Then
    13.     Private Const PTR_SIZE                  As Long = 8
    14. #Else
    15.     Private Const PTR_SIZE                  As Long = 4
    16.     Private Const SIGN_BIT                  As Long = &H80000000
    17. #End If
    18. '--- for CompareStringW
    19. Private Const LOCALE_USER_DEFAULT           As Long = &H400
    20. Private Const NORM_IGNORECASE               As Long = 1
    21. Private Const CSTR_LESS_THAN                As Long = 1
    22. Private Const CSTR_EQUAL                    As Long = 2
    23. Private Const CSTR_GREATER_THAN             As Long = 3
    24.  
    25. #If HasPtrSafe Then
    26.     Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    27.     Private Declare PtrSafe Function CompareStringW Lib "kernel32" (ByVal Locale As Long, ByVal dwCmpFlags As Long, lpString1 As Any, ByVal cchCount1 As Long, lpString2 As Any, ByVal cchCount2 As Long) As Long
    28. #Else
    29.     Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    30.     Private Declare Function CompareStringW Lib "kernel32" (ByVal Locale As Long, ByVal dwCmpFlags As Long, lpString1 As Any, ByVal cchCount1 As Long, lpString2 As Any, ByVal cchCount2 As Long) As Long
    31. #End If
    32.  
    33. #If Win64 Then
    34.     Private Type VbCollectionHeader
    35.         pInterface1         As LongPtr  '  &H00
    36.         pInterface2         As LongPtr  '  &H08
    37.         pInterface3         As LongPtr  '  &H10
    38.         lRefCounter         As Long     '  &H18
    39.         Count               As Long     '  &H1C
    40.         pvUnk1              As LongPtr  '  &H20
    41.         pFirstIndexedItem   As LongPtr  '  &H28
    42.         pLastIndexedItem    As LongPtr  '  &H30
    43.         pvUnk4              As LongPtr  '  &H38
    44.         pRootTreeItem       As LongPtr  '  &H40
    45.         pEndTreePtr         As LongPtr  '  &H48
    46.         pvUnk5              As LongPtr  '  &H50
    47.     End Type                            '  &H58
    48.    
    49.     Private Type VbCollectionItem
    50.         Data                As Variant  '  &H00
    51.         KeyPtr              As LongPtr  '  &H18
    52.         pPrevIndexedItem    As LongPtr  '  &H20
    53.         pNextIndexedItem    As LongPtr  '  &H28
    54.     '    pvUnknown           As LongPtr
    55.         pParentItem         As LongPtr  '  &H30
    56.         pRightBranch        As LongPtr  '  &H38
    57.         pLeftBranch         As LongPtr  '  &H40
    58.         bFlag               As Boolean  '  &H48
    59.     End Type                            '  &H4C
    60.    
    61.     Private Enum VbCollectionOffsets
    62.         o_pFirstIndexedItem = &H28
    63.         o_pRootTreeItem = &H40
    64.         o_pEndTreePtr = &H48
    65.         '--- item
    66.         o_KeyPtr = &H18
    67.         o_pNextIndexedItem = o_pFirstIndexedItem '--- Coincidence?
    68.         o_pRightBranch = &H38
    69.         o_pLeftBranch = &H40
    70.     End Enum
    71. #Else
    72.     Private Type VbCollectionHeader
    73.         pInterface1         As Long   '  &H00
    74.         pInterface2         As Long   '  &H04
    75.         pInterface3         As Long   '  &H08
    76.         lRefCounter         As Long   '  &H0C
    77.         Count               As Long   '  &H10
    78.         pvUnk1              As Long   '  &H14
    79.         pFirstIndexedItem   As Long   '  &H18
    80.         pLastIndexedItem    As Long   '  &H1C
    81.         pvUnk4              As Long   '  &H20
    82.         pRootTreeItem       As Long   '  &H24
    83.         pEndTreePtr         As Long   '  &H28
    84.         pvUnk5              As Long   '  &H2C
    85.     End Type                          '  &H30
    86.    
    87.     Private Type VbCollectionItem
    88.         Data                As Variant  '  &H00
    89.         KeyPtr              As Long     '  &H10
    90.         pPrevIndexedItem    As Long     '  &H14
    91.         pNextIndexedItem    As Long     '  &H18
    92.         pvUnknown           As Long     '  &H1C
    93.         pParentItem         As Long     '  &H20
    94.         pRightBranch        As Long     '  &H24
    95.         pLeftBranch         As Long     '  &H28
    96.         bFlag               As Boolean  '  &H2C
    97.     End Type                            '  &H30
    98.    
    99.     Private Enum VbCollectionOffsets
    100.         o_pFirstIndexedItem = &H18
    101.         o_pRootTreeItem = &H24
    102.         o_pEndTreePtr = &H28
    103.         '--- item
    104.         o_KeyPtr = &H10
    105.         o_pNextIndexedItem = o_pFirstIndexedItem '--- Again?
    106.         o_pRightBranch = &H24
    107.         o_pLeftBranch = &H28
    108.     End Enum
    109. #End If
    110.  
    111. Public Function CollectionAllKeys(oCol As Collection) As String()
    112.     #If HasPtrSafe Then
    113.         Dim lPtr        As LongPtr
    114.     #Else
    115.         Dim lPtr        As Long
    116.     #End If
    117.     Dim aRetVal()       As String
    118.     Dim lIdx            As Long
    119.     Dim sTemp           As String
    120.    
    121.     If oCol.Count = 0 Then
    122.         aRetVal = Split(vbNullString)
    123.     Else
    124.         ReDim aRetVal(1 To oCol.Count) As String
    125.         lPtr = ObjPtr(oCol)
    126.         For lIdx = 1 To UBound(aRetVal)
    127.             #If LargeAddressAware Then
    128.                 Call CopyMemory(lPtr, ByVal (lPtr Xor SIGN_BIT) + o_pNextIndexedItem Xor SIGN_BIT, PTR_SIZE)
    129.                 Call CopyMemory(ByVal VarPtr(sTemp), ByVal (lPtr Xor SIGN_BIT) + o_KeyPtr Xor SIGN_BIT, PTR_SIZE)
    130.             #Else
    131.                 Call CopyMemory(lPtr, ByVal lPtr + o_pNextIndexedItem, PTR_SIZE)
    132.                 Call CopyMemory(ByVal VarPtr(sTemp), ByVal lPtr + o_KeyPtr, PTR_SIZE)
    133.             #End If
    134.             aRetVal(lIdx) = sTemp
    135.         Next
    136.         Call CopyMemory(ByVal VarPtr(sTemp), NULL_PTR, PTR_SIZE)
    137.     End If
    138.     CollectionAllKeys = aRetVal
    139. End Function
    140.  
    141. Public Function CollectionKeyByIndex(oCol As Collection, ByVal lIdx As Long) As String
    142.     #If HasPtrSafe Then
    143.         Dim lPtr        As LongPtr
    144.     #Else
    145.         Dim lPtr        As Long
    146.     #End If
    147.     Dim sTemp           As String
    148.    
    149.     If lIdx >= 1 And lIdx <= oCol.Count Then
    150.         lPtr = ObjPtr(oCol)
    151.         For lIdx = 1 To lIdx
    152.             #If LargeAddressAware Then
    153.                 Call CopyMemory(lPtr, ByVal (lPtr Xor SIGN_BIT) + o_pNextIndexedItem Xor SIGN_BIT, PTR_SIZE)
    154.             #Else
    155.                 Call CopyMemory(lPtr, ByVal lPtr + o_pNextIndexedItem, PTR_SIZE)
    156.             #End If
    157.         Next
    158.         #If LargeAddressAware Then
    159.             Call CopyMemory(ByVal VarPtr(sTemp), ByVal (lPtr Xor SIGN_BIT) + o_KeyPtr Xor SIGN_BIT, PTR_SIZE)
    160.         #Else
    161.             Call CopyMemory(ByVal VarPtr(sTemp), ByVal lPtr + o_KeyPtr, PTR_SIZE)
    162.         #End If
    163.         CollectionKeyByIndex = sTemp
    164.         Call CopyMemory(ByVal VarPtr(sTemp), NULL_PTR, PTR_SIZE)
    165.     End If
    166. End Function
    167.  
    168. Public Function CollectionIndexByKey(oCol As Collection, sKey As String, Optional ByVal IgnoreCase As Boolean = True) As Long
    169.     #If HasPtrSafe Then
    170.         Dim lItemPtr    As LongPtr
    171.         Dim lEofPtr     As LongPtr
    172.         Dim lPtr        As LongPtr
    173.     #Else
    174.         Dim lItemPtr    As Long
    175.         Dim lEofPtr     As Long
    176.         Dim lPtr        As Long
    177.     #End If
    178.     Dim sTemp           As String
    179.    
    180.     If Not oCol Is Nothing Then
    181.         #If LargeAddressAware Then
    182.             Call CopyMemory(lItemPtr, ByVal (ObjPtr(oCol) Xor SIGN_BIT) + o_pRootTreeItem Xor SIGN_BIT, PTR_SIZE)
    183.             Call CopyMemory(lEofPtr, ByVal (ObjPtr(oCol) Xor SIGN_BIT) + o_pEndTreePtr Xor SIGN_BIT, PTR_SIZE)
    184.         #Else
    185.             Call CopyMemory(lItemPtr, ByVal ObjPtr(oCol) + o_pRootTreeItem, PTR_SIZE)
    186.             Call CopyMemory(lEofPtr, ByVal ObjPtr(oCol) + o_pEndTreePtr, PTR_SIZE)
    187.         #End If
    188.     End If
    189.     Do While lItemPtr <> lEofPtr
    190.         #If LargeAddressAware Then
    191.             Call CopyMemory(ByVal VarPtr(sTemp), ByVal (lItemPtr Xor SIGN_BIT) + o_KeyPtr Xor SIGN_BIT, PTR_SIZE)
    192.         #Else
    193.             Call CopyMemory(ByVal VarPtr(sTemp), ByVal lItemPtr + o_KeyPtr, PTR_SIZE)
    194.         #End If
    195.         Select Case CompareStringW(LOCALE_USER_DEFAULT, -IgnoreCase * NORM_IGNORECASE, ByVal StrPtr(sKey), Len(sKey), ByVal StrPtr(sTemp), Len(sTemp))
    196.         Case CSTR_LESS_THAN
    197.             #If LargeAddressAware Then
    198.                 Call CopyMemory(lItemPtr, ByVal (lItemPtr Xor SIGN_BIT) + o_pLeftBranch Xor SIGN_BIT, PTR_SIZE)
    199.             #Else
    200.                 Call CopyMemory(lItemPtr, ByVal lItemPtr + o_pLeftBranch, PTR_SIZE)
    201.             #End If
    202.         Case CSTR_GREATER_THAN
    203.             #If LargeAddressAware Then
    204.                 Call CopyMemory(lItemPtr, ByVal (lItemPtr Xor SIGN_BIT) + o_pRightBranch Xor SIGN_BIT, PTR_SIZE)
    205.             #Else
    206.                 Call CopyMemory(lItemPtr, ByVal lItemPtr + o_pRightBranch, PTR_SIZE)
    207.             #End If
    208.         Case CSTR_EQUAL
    209.             lPtr = ObjPtr(oCol)
    210.             Do While lPtr <> lItemPtr
    211.                 #If LargeAddressAware Then
    212.                     Call CopyMemory(lPtr, ByVal (lPtr Xor SIGN_BIT) + o_pNextIndexedItem Xor SIGN_BIT, PTR_SIZE)
    213.                 #Else
    214.                     Call CopyMemory(lPtr, ByVal lPtr + o_pNextIndexedItem, PTR_SIZE)
    215.                 #End If
    216.                 CollectionIndexByKey = CollectionIndexByKey + 1
    217.             Loop
    218.             GoTo QH
    219.         Case Else
    220.             Call CopyMemory(ByVal VarPtr(sTemp), NULL_PTR, PTR_SIZE)
    221.             Err.Raise vbObjectError, , "Unexpected result from CompareStringW"
    222.         End Select
    223.     Loop
    224. QH:
    225.     Call CopyMemory(ByVal VarPtr(sTemp), NULL_PTR, PTR_SIZE)
    226. End Function
    227.  
    228. Public Function CollectionSortedKeys(oCol As Collection) As String()
    229.     #If HasPtrSafe Then
    230.         Dim lItemPtr    As LongPtr
    231.         Dim lEofPtr     As LongPtr
    232.     #Else
    233.         Dim lItemPtr    As Long
    234.         Dim lEofPtr     As Long
    235.     #End If
    236.     Dim aRetVal()       As String
    237.     Dim lCount          As Long
    238.    
    239.     If Not oCol Is Nothing Then
    240.         #If LargeAddressAware Then
    241.             Call CopyMemory(lItemPtr, ByVal (ObjPtr(oCol) Xor SIGN_BIT) + o_pRootTreeItem Xor SIGN_BIT, PTR_SIZE)
    242.             Call CopyMemory(lEofPtr, ByVal (ObjPtr(oCol) Xor SIGN_BIT) + o_pEndTreePtr Xor SIGN_BIT, PTR_SIZE)
    243.         #Else
    244.             Call CopyMemory(lItemPtr, ByVal ObjPtr(oCol) + o_pRootTreeItem, PTR_SIZE)
    245.             Call CopyMemory(lEofPtr, ByVal ObjPtr(oCol) + o_pEndTreePtr, PTR_SIZE)
    246.         #End If
    247.     End If
    248.     If lItemPtr <> lEofPtr Then
    249.         ReDim aRetVal(1 To oCol.Count) As String
    250.         pvTraverseInorder lItemPtr, lEofPtr, aRetVal, lCount
    251.     End If
    252.     If lCount = 0 Then
    253.         aRetVal = Split(vbNullString)
    254.     ElseIf lCount < oCol.Count Then
    255.         ReDim Preserve aRetVal(1 To lCount) As String
    256.     End If
    257.     CollectionSortedKeys = aRetVal
    258. End Function
    259.  
    260. #If HasPtrSafe Then
    261. Private Sub pvTraverseInorder(ByVal lItemPtr As LongPtr, ByVal lEofPtr As LongPtr, aRetVal() As String, lIdx As Long)
    262. #Else
    263. Private Sub pvTraverseInorder(ByVal lItemPtr As Long, ByVal lEofPtr As Long, aRetVal() As String, lIdx As Long)
    264. #End If
    265.     #If HasPtrSafe Then
    266.         Dim lPtr        As LongPtr
    267.     #Else
    268.         Dim lPtr        As Long
    269.     #End If
    270.     Dim sTemp           As String
    271.    
    272.     '--- traverse left branch if present
    273.     #If LargeAddressAware Then
    274.         Call CopyMemory(lPtr, ByVal (lItemPtr Xor SIGN_BIT) + o_pLeftBranch Xor SIGN_BIT, PTR_SIZE)
    275.     #Else
    276.         Call CopyMemory(lPtr, ByVal lItemPtr + o_pLeftBranch, PTR_SIZE)
    277.     #End If
    278.     If lPtr <> lEofPtr Then
    279.         pvTraverseInorder lPtr, lEofPtr, aRetVal, lIdx
    280.     End If
    281.     '--- collect current key
    282.     #If LargeAddressAware Then
    283.         Call CopyMemory(ByVal VarPtr(sTemp), ByVal (lItemPtr Xor SIGN_BIT) + o_KeyPtr Xor SIGN_BIT, PTR_SIZE)
    284.     #Else
    285.         Call CopyMemory(ByVal VarPtr(sTemp), ByVal lItemPtr + o_KeyPtr, PTR_SIZE)
    286.     #End If
    287.     lIdx = lIdx + 1
    288.     aRetVal(lIdx) = sTemp
    289.     Call CopyMemory(ByVal VarPtr(sTemp), NULL_PTR, PTR_SIZE)
    290.     '--- traverse right branch if present
    291.     #If LargeAddressAware Then
    292.         Call CopyMemory(lPtr, ByVal (lItemPtr Xor SIGN_BIT) + o_pRightBranch Xor SIGN_BIT, PTR_SIZE)
    293.     #Else
    294.         Call CopyMemory(lPtr, ByVal lItemPtr + o_pRightBranch, PTR_SIZE)
    295.     #End If
    296.     If lPtr <> lEofPtr Then
    297.         pvTraverseInorder lPtr, lEofPtr, aRetVal, lIdx
    298.     End If
    299. End Sub
    300.  
    301. #If False Then
    302. Public Sub Test()
    303.     Dim oCol As New Collection
    304.     oCol.Add "aaaccc", "ccc"
    305.     oCol.Add "aaaaaa", "aaa"
    306.     oCol.Add "aaa"
    307.     oCol.Add "aaabbb", "bbb"
    308.     oCol.Add "test", vbNullString
    309.     Debug.Print CollectionKeyByIndex(oCol, 1), "["; CollectionKeyByIndex(oCol, 10) & "]", StrPtr(CollectionKeyByIndex(oCol, 10))
    310.     Debug.Print CollectionIndexByKey(oCol, "aaa"), CollectionIndexByKey(oCol, "AAA")
    311.     Debug.Print CollectionIndexByKey(oCol, "ddd"), CollectionIndexByKey(oCol, "aaA", IgnoreCase:=False)
    312.     Debug.Print CollectionIndexByKey(oCol, ""), "["; CollectionKeyByIndex(oCol, 5); "]", StrPtr(CollectionKeyByIndex(oCol, 5))
    313.     Debug.Print Join(CollectionAllKeys(oCol), ",")
    314.     Debug.Print Join(CollectionSortedKeys(oCol), ",")
    315. End Sub
    316. #End If
    cheers,
    </wqw>

  2. #2
    Hyperactive Member
    Join Date
    Aug 2017
    Posts
    380

    Re: [VB6/VBA] Collection keys

    There is a more elegant way of getting a string from a pointer. Also, dereferencing that pointer probably isn't really necessary because the KeyPtr member of the VbCollectionItem structure is apparently a BSTR.

  3. #3

    Thread Starter
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,154

    Re: [VB6/VBA] Collection keys

    Can you tell me exactly which one derefencing method do you mean? Mind that keys are BSTRs and can contain '\0' chars so it has to be SysAllocStringByteLen based.

    I'm not using the structs in the code. They are included only to document the offsets for x64 and i386 and can be safely removed. The snippet is using offsets from VbCollectionOffsets for direct pointer arithmetic.

    The interesting part for VB6 coders is VBA's new PtrSafe declare's for both x64 and 32-bit declares, LongPtr for 4 vs 8-byte wide pointers, Win64 conditional compilation and the derivative PTR_SIZE and NULL_PTR to handle pointers invariantly to bitness.

    Also here is the ArrPtr 64-bit declare:
    Code:
    Private Declare PtrSafe Function ArrPtr Lib "vbe7" Alias "VarPtr" (Ptr() As Any) As LongPtr
    Edit: Notice also that sizeof VARIANT struct has increased from 16 to 24 bytes.

    cheers,
    </wqw>

  4. #4
    Hyperactive Member
    Join Date
    Aug 2017
    Posts
    380

    Re: [VB6/VBA] Collection keys

    Quote Originally Posted by wqweto View Post
    Can you tell me exactly which one derefencing method do you mean? Mind that keys are BSTRs and can contain '\0' chars so it has to be SysAllocStringByteLen based.
    You're right. SysAllocString/SysReAllocString will fail if the string contains embedded vbNullChar(s). In that case, SysReAllocStringLen+SysStringLen should be used.

  5. #5
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,936

    Re: [VB6/VBA] Collection keys

    Cool stuff Wqweto.

    I tend to try and keep all my code in VB6, but there is one specific Excel file I use that'll always have a substantial amount of VBA code on it. At present, I don't make any use of the Collection class in it, but I could see myself doing that in the future. Also, I could see myself willy-nilly pulling some of the Collection sort procedures into it, not thinking about the 64-bit situation. In fact, I hadn't even thought about Variants being 24 bytes in a 64-bit environment.

    All this just makes me pine for a stand-alone COM based VB7 though.

    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.

  6. #6

    Thread Starter
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,154

    Re: [VB6/VBA] Collection keys

    Just added CollectionIndexByKey function that can be used for *case-sensitive* key existence check too.

    cheers,
    </wqw>

  7. #7
    PowerPoster
    Join Date
    Jun 2015
    Posts
    2,224

    Re: [VB6/VBA] Collection keys

    Not to complicate things, but patched versions of 32bit office are LAA.

  8. #8

    Thread Starter
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,154

    Re: [VB6/VBA] Collection keys

    Are these common? I think x64 offices are more common than 32-bit versions nowadays and so the incentive to deal w/ all the trouble of being flagged LARGEADDRESSAWARE is diminishing IMO.

    For now I prefer to leave reducing LargeAddressAware const to #Const LargeAddressAware = (Win64 = 0) an open question and at the discretions of this module's end-users.

    cheers,
    </wqw>

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

    Re: [VB6/VBA] Collection keys

    Quote Originally Posted by wqweto View Post
    I think x64 offices are more common than 32-bit versions nowadays
    Hey Wqweto, that's certainly not the world I live in. Many of the Windows OS's are 64-bit, but Office is lagging behind that quite badly. I'm always working in hospital environments (specifically, motion analysis laboratories), and they seem to always have site licenses for Office. I've got no idea how that works, and I've never asked. But they just keep installing 32-bit Office on all their new machines.

    In fact, so far, the only time I've run into Office 64-bit is on the personal laptops of various researchers who work with the hospitals. I'm not sure I've even seen a version of Office 64-bit on any of the computers I see in the hospitals.

    Just Sharing,
    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.

  10. #10
    PowerPoster
    Join Date
    Jun 2015
    Posts
    2,224

    Re: [VB6/VBA] Collection keys

    originally the best practice was to install 32bit office in enterprise environments mostly due to compatibility with all the existing plugins and ODBC drivers. Someday that may change - when all those legacy adapters get updated for 64bit? We've got Office 365 at 32bit here.

  11. #11

    Thread Starter
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,154

    Re: [VB6/VBA] Collection keys

    Unfortunately MS again missed to implement LongPtr w/ unsigned semantics or at least they could have just made the compiler remain silent on &7FFFFFFF overflow.

    Such a great opportunity to impl true 4GB address arithmetics on the new type and they just aliased it to Long probably impl w/ the least efforts possible but didn't think twice before breaking backwards comp w/ PtrSafe declares -- all the client code has to be refactored w/ conditional compilation is not their problem.

    cheers,
    </wqw>
    p.s. I just checked LongPtr arith on 32-bit Excel Build 15.0.4833.1000 that is supposed to be *the* LAA version.

  12. #12
    PowerPoster
    Join Date
    Jan 2020
    Posts
    3,749

    Re: [VB6/VBA] Collection keys

    Why are you able to understand the internal structure of these Collection types? Did you decompile him?

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