Results 1 to 30 of 30

Thread: VB6 - Returning/Detecting Empty Arrays

  1. #1

    Thread Starter
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,471

    VB6 - Returning/Detecting Empty Arrays

    Lots of times you need to create a function, property, method, etc. that returns an array. But there are cases where you have "nothing to return" and you'd like to return an "empty" array.

    Sometimes an empty array result might be a valid condition. Or maybe you want to use it to signal an error condition of some kind.


    The usual approaches require that the caller rely on exception handling to detect this "emptiness" but at least for Byte arrays and Variant arrays there are a couple of tricks you can use:

    Code:
    Option Explicit
    
    Private B() As Byte
    Private V() As Variant
    
    '---------------------------------------------------------------
    'Creating empty arrays.  Just do this inline in real programs,
    'you don't need these functions:
    
    Private Function MakeEmptyB() As Byte()
        MakeEmptyB = ""
    End Function
    
    Private Function MakeEmptyV() As Variant()
        MakeEmptyV = Array()
    End Function
    
    '---------------------------------------------------------------
    'Testing for empty arrays.  Just do this inline in real programs,
    'you don't need these functions:
    
    Private Function IsEmptyB(ByRef Bytes() As Byte) As Boolean
        IsEmptyB = UBound(Bytes) < LBound(Bytes)
    End Function
    
    Private Function IsEmptyV(ByRef Variants() As Variant) As Boolean
        IsEmptyV = UBound(Variants) < LBound(Variants)
    End Function
    
    '---------------------------------------------------------------
    'Do tests with error trapping, printing results on the Form:
    
    Private Sub PerformTests()
        On Error Resume Next
        Print IsEmptyB(B)
        If Err Then Print Err.Number, Err.Description
        Err.Clear
        Print IsEmptyV(V)
        If Err Then Print Err.Number, Err.Description
        On Error GoTo 0
    End Sub
    
    Private Sub Form_Load()
        AutoRedraw = True
    
        'Doesn't work (subscript out of range errors):
        Erase B
        Erase V
        PerformTests
    
        Print
    
        'Works:
        B = MakeEmptyB()
        V = MakeEmptyV()
        PerformTests
    End Sub
    If the arrays you would normally return would have bounds greater than or equal to zero (0) then you can simplify the "tests" by checking for UBound = -1, which is what these approaches (both Byte and Variant arrays) will return.

    As suggested in the comments in the code above, it usually isn't worth writing these functions. Just use the one-line code inline where you need it.


    If there is an equivalent for other array types I haven't found it. Perhaps you know of a trick for Long, Single, UDT, or other types and can post it here.
    Last edited by dilettante; Sep 28th, 2013 at 04:47 PM. Reason: typo corrected

  2. #2
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,075

    Re: VB6 - Returning/Detecting Empty Arrays

    Something to add to the pile which works for String-Arrays - in VB6 and VBA (VB5 doesn't have the Split-function):

    Code:
    Private Function MakeEmptyS() As String()
        MakeEmptyS= Split("")
    End Function
    BTW, small typo in your: "... simplify the "tests" by checking for LBound = -1"
    it's the Ubound, which is smaller than the LBound "by one".

    Olaf

  3. #3

    Thread Starter
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,471

    Re: VB6 - Returning/Detecting Empty Arrays

    Good catch, I'll change that.

    Thanks for the String array trick, another useful one!

  4. #4
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    4,902

    Re: VB6 - Returning/Detecting Empty Arrays

    You can alias `SafeArrayCreateVector` API function directly like this
    Code:
    Private Declare Function EmptyVariantArray Lib "oleaut32" Alias "SafeArrayCreateVector" (Optional ByVal vt As VbVarType = vbVariant, Optional ByVal lLow As Long = 0, Optional ByVal lCount As Long = 0) As Variant()
    Private Declare Function EmptyStringArray Lib "oleaut32" Alias "SafeArrayCreateVector" (Optional ByVal vt As VbVarType = vbString, Optional ByVal lLow As Long = 0, Optional ByVal lCount As Long = 0) As String()
    Private Declare Function EmptyByteArray Lib "oleaut32" Alias "SafeArrayCreateVector" (Optional ByVal vt As VbVarType = vbByte, Optional ByVal lLow As Long = 0, Optional ByVal lCount As Long = 0) As Byte()
    Private Declare Function EmptyLongArray Lib "oleaut32" Alias "SafeArrayCreateVector" (Optional ByVal vt As VbVarType = vbLong, Optional ByVal lLow As Long = 0, Optional ByVal lCount As Long = 0) As Long()
    Private Declare Function EmptyDoubleArray Lib "oleaut32" Alias "SafeArrayCreateVector" (Optional ByVal vt As VbVarType = vbDouble, Optional ByVal lLow As Long = 0, Optional ByVal lCount As Long = 0) As Double()
    Another meaning of "empty" array can be an unallocated one. If you declare an array with `Dim baBuffer() As Byte` there is no array allocated and `U/LBound` functions cannot be used. There is an API hack to test for these
    Code:
    Private Declare Function ArrPtr Lib "msvbvm60" Alias "VarPtr" (Ptr() As Any) As Long
    
    Public Function Peek(ByVal lPtr As Long) As Long
        Call CopyMemory(Peek, ByVal lPtr, 4)
    End Function
    
    '--- test for unallocated array
    If Peek(ArrPtr(baBuffer)) <> 0 Then
       ...
    This test can be used with arrays of UDTs too.

    Sometimes it's useful to determine array dimensions for a Variant parameter at run-time e.g. a 2D array allocated with `ReDim vBuffer(0 to 10, 0 to 20)`. I'm using this `GetArrayDimension` function
    Code:
    Public Function GetArrayDimension(vArray As Variant) As Long
        Const VT_BYREF      As Long = &H4000
        Dim lPtr            As Long
        
        If IsArray(vArray) Then
            lPtr = Peek(VarPtr(vArray) + 8)
            If (PeekInt(VarPtr(vArray)) And VT_BYREF) <> 0 Then
                lPtr = Peek(lPtr)
            End If
            If lPtr <> 0 Then
                GetArrayDimension = PeekInt(lPtr)
            End If
        End If
    End Function
    
    Public Function Peek(ByVal lPtr As Long) As Long
        Call CopyMemory(Peek, ByVal lPtr, 4)
    End Function
    
    Public Function PeekInt(ByVal lPtr As Long) As Integer
        Call CopyMemory(PeekInt, ByVal lPtr, 2)
    End Function
    A nice side-effect is that calling `GetArrayDimension` with unallocated arrays returns 0 because the last `If lPtr <> 0 Then` test fails.

    cheers,
    </wqw>
    Last edited by wqweto; Oct 6th, 2013 at 02:34 PM.

  5. #5
    New Member
    Join Date
    Oct 2013
    Posts
    2

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by dilettante View Post
    Thanks for the String array trick, another useful one!
    Another trick which seems to work, is simply:

    (Not MyAry)

    As in:

    Code:
        Dim ary() As Variant
        Dim b As Boolean
        
        b = (Not ary) <> -1
        Debug.Print "IsDimensioned: " & CStr(b)
        
        ReDim ary(1) As Variant
    
        b = (Not ary) <> -1
        Debug.Print "IsDimensioned: " & CStr(b)

  6. #6
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,075

    Re: VB6 - Returning/Detecting Empty Arrays

    The Not (Not Array) trickery is wellknown - but it should be wellknown too, that this method destabilizes VB
    (not really sure what happens under the hood there - but something definitely does not work "according to plan".

    Check this out in a fresh loaded, empty VB-Form-Project.

    Code:
    Private Sub Form_Load()
    Dim Arr()
      Debug.Print (Not Arr) <> -1
      Debug.Print 12 / 3 ' it will give error here (16 - "Expression too complex")
    End Sub
    Others (in old Newsgroup-posts) reported these "Expression too complex" errors
    happening even somewhat delayed (in a completely different place or function) -
    but on asking, if "somewhere else in the App" the Not Not Array-Test was used,
    the answer was Yes" ... after changing to a different "IsDimensioned"-check the
    occasionally happening "Expression too complex" errors went away.

    Just for completeness, the simple Function below works with all non-UDT-typed VBArrays
    and (when placed in a *.bas) should be enough for most purposes:
    Code:
    Function IsDimmed(Arr As Variant) As Boolean
    On Error GoTo ReturnFalse
      IsDimmed = UBound(Arr) >= LBound(Arr)
    ReturnFalse:
    End Function
    Olaf
    Last edited by Schmidt; Oct 18th, 2013 at 04:31 AM.

  7. #7
    Angel of Code Niya's Avatar
    Join Date
    Nov 2011
    Posts
    8,510

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by Schmidt View Post
    Just for completeness, the simple Function below works with all non-UDT-typed VBArrays
    and (when placed in a *.bas) should be enough for most purposes:
    Code:
    Function IsDimmed(Arr As Variant) As Boolean
    On Error GoTo ReturnFalse
      IsDimmed = UBound(Arr) >= LBound(Arr)
    ReturnFalse:
    End Function
    Olaf
    I used a very similar technique in my later VB6 programs to detect empty arrays. I absolutely hated that. I always wondered why they didn't just provide a damn Count function. The OLE API probably has something to do just that but I'm wasn't going to go through the trouble of having to declare SAFEARRAYs and their entourage just to check for an empty array. Like needing a hammer to swat a fly.
    Treeview with NodeAdded/NodesRemoved events | BlinkLabel control | Calculate Permutations | Object Enums | ComboBox with centered items | .Net Internals article(not mine) | Wizard Control | Understanding Multi-Threading | Simple file compression | Demon Arena

    Copy/move files using Windows Shell | I'm not wanted

    C++ programmers will dismiss you as a cretinous simpleton for your inability to keep track of pointers chained 6 levels deep and Java programmers will pillory you for buying into the evils of Microsoft. Meanwhile C# programmers will get paid just a little bit more than you for writing exactly the same code and VB6 programmers will continue to whitter on about "footprints". - FunkyDexter

    There's just no reason to use garbage like InputBox. - jmcilhinney

    The threads I start are Niya and Olaf free zones. No arguing about the benefits of VB6 over .NET here please. Happiness must reign. - yereverluvinuncleber

  8. #8
    Hyperactive Member
    Join Date
    Nov 2011
    Posts
    472

    Re: VB6 - Returning/Detecting Empty Arrays

    i use

    Public Declare Function SafeArrayGetDim Lib "oleaut32.dll" (ByRef saArray() As Any) As Long

    if SafeArrayGetDim(arrayname) > 0 then
    'Array returned
    else
    ' No array
    end if
    Last edited by k_zeon; Oct 20th, 2013 at 10:34 AM.

  9. #9
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,075

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by k_zeon View Post
    i use

    Public Declare Function SafeArrayGetDim Lib "oleaut32.dll" (ByRef saArray() As Any) As Long

    if SafeArrayGetDim(arrayname) > 0 then
    'Array returned
    else
    ' No array
    end if
    Careful here, because this function when called this way (handing over the Array-Variable directly), is misused - because it doesn't expect the "VarPtr" of the Array-Variable,
    but the SafeArray-Pointer instead (one level down the reference-stack).
    You can easily see that, because in case of a returned-Value <> 0, it is in no way the Dimension you get back, but the first 16 Bits of the SafeArray-Pointer.

    It works (somewhat) - but there's an (albeit small) chance that the SafeArray-Pointer has a value, with the first 16Bits "all zero" - and in this case you
    have an initialized Array - but your function would report a Zero (wrongly signalizing an uninitialized state).

    Olaf

  10. #10
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    4,902

    Re: VB6 - Returning/Detecting Empty Arrays

    Here is a sample how to use `SafeArrayGetDim` to get array dimensions
    Code:
    Option Explicit
    
    Private Type PeekArrayType
        Ptr         As Long
        Reserved    As Currency
    End Type
    
    Private Declare Function PeekArray Lib "kernel32" Alias "RtlMoveMemory" (Arr() As Any, Optional ByVal Length As Long = 4) As PeekArrayType
    Private Declare Function SafeArrayGetDim Lib "oleaut32.dll" (ByVal Ptr As Long) As Long
    
    Private Type CustomType
        CustomValues(0 To 10) As Long
    End Type
    
    Private Sub Form_Load()
        Dim aLong()     As Long
        Dim aUdt()      As CustomType
        
        Debug.Print "Test if allocated: "; PeekArray(aLong).Ptr <> 0, "Expected: "; False
        Debug.Print "Array dimensions: "; SafeArrayGetDim(PeekArray(aLong).Ptr), "Expected: "; 0
        
        Debug.Print "Test if allocated: "; PeekArray(aUdt).Ptr <> 0, "Expected: "; False
        Debug.Print "Array dimensions: "; SafeArrayGetDim(PeekArray(aUdt).Ptr), "Expected: "; 0
        
        ReDim aLong(0 To 10, 0 To 20) As Long
        ReDim aUdt(0 To 10) As CustomType
        Debug.Print "After redim..."
        
        Debug.Print "Test if allocated: "; PeekArray(aLong).Ptr <> 0, "Expected: "; True
        Debug.Print "Array dimensions: "; SafeArrayGetDim(PeekArray(aLong).Ptr), "Expected: "; 2
        
        Debug.Print "Test if allocated: "; PeekArray(aUdt).Ptr <> 0, "Expected: "; True
        Debug.Print "Array dimensions: "; SafeArrayGetDim(PeekArray(aUdt).Ptr), "Expected: "; 1
    End Sub
    `PeekArray` can be used to test if an array (of any type) is allocated and is based on the this flexible `Peek` implementation

    Code:
    Option Explicit
    
    Private Type PeekType
        Value       As Long
        Reserved    As Currency
    End Type
    
    Private Declare Function Peek Lib "kernel32" Alias "RtlMoveMemory" (ByVal Ptr As Long, Optional ByVal Length As Long = 4) As PeekType
    
    Private Sub Form_Load()
        Dim lValue      As Long
        Dim lPtr        As Long
        
        lValue = &HDEADBEEF
        lPtr = VarPtr(lValue)
        Debug.Print Hex(Peek(lPtr).Value), "Expected: "; Hex(&HDEADBEEF) '-- peek long
        Debug.Print Hex(Peek(lPtr, 2).Value), "Expected: "; Hex(&HBEEF)  '-- peek int
        Debug.Print Hex(Peek(lPtr, 1).Value), "Expected: "; Hex(&HEF)    '-- peek byte
    End Sub
    This method can be further extended to access SAFEAARRAY struct directly

    Code:
    Private Type SafeArraySingleDimensionType
        cDims       As Integer      '--- usually 1
        fFeatures   As Integer      '--- leave 0
        cbElements  As Long         '--- bytes per element (2-int, 4-long)
        cLocks      As Long         '--- leave 0
        pvData      As Long         '--- ptr to data
        cElements   As Long         '--- UBound + 1
        lLbound     As Long         '--- LBound
    End Type
    
    Private Declare Function PeekSafeArray Lib "kernel32" Alias "RtlMoveMemory" (ByVal Ptr As Long, Optional ByVal Length As Long = 24) As SafeArraySingleDimensionType
    
    Private Sub Form_Load()
        Dim aTemp(0 To 10)      As Long
        
        Debug.Print PeekSafeArray(PeekArray(aTemp).Ptr).cDims, "Expected: "; 1
    End Sub
    While researching UDT as retvals of an API declare I found this interesting way to access hi/lo-words

    Code:
    Option Explicit
    
    Private Type DWordPartsType
        LoWord  As Integer
        HiWord  As Integer
    End Type
    
    Private Declare Function DWordParts Lib "msvbvm60" Alias "VarPtr" (ByVal dwValue As Long) As DWordPartsType
    
    Private Sub Form_Load()
        With DWordParts(&H12345678)
            Debug.Print Hex(.LoWord), "Expected: "; Hex(&H5678)
            Debug.Print Hex(.HiWord), "Expected: "; Hex(&H1234)
        End With
    End Sub
    cheers,
    </wqw>

  11. #11
    Frenzied Member
    Join Date
    Jan 2010
    Posts
    1,103

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by dilettante View Post
    Lots of times you need to create a function, property, method, etc. that returns an array. But there are cases where you have "nothing to return" and you'd like to return an "empty" array.

    Sometimes an empty array result might be a valid condition. Or maybe you want to use it to signal an error condition of some kind.


    The usual approaches require that the caller rely on exception handling to detect this "emptiness" but at least for Byte arrays and Variant arrays there are a couple of tricks you can use:

    Code:
    Option Explicit
    
    Private B() As Byte
    Private V() As Variant
    
    '---------------------------------------------------------------
    'Creating empty arrays.  Just do this inline in real programs,
    'you don't need these functions:
    
    Private Function MakeEmptyB() As Byte()
        MakeEmptyB = ""
    End Function
    
    Private Function MakeEmptyV() As Variant()
        MakeEmptyV = Array()
    End Function
    
    '---------------------------------------------------------------
    'Testing for empty arrays.  Just do this inline in real programs,
    'you don't need these functions:
    
    Private Function IsEmptyB(ByRef Bytes() As Byte) As Boolean
        IsEmptyB = UBound(Bytes) < LBound(Bytes)
    End Function
    
    Private Function IsEmptyV(ByRef Variants() As Variant) As Boolean
        IsEmptyV = UBound(Variants) < LBound(Variants)
    End Function
    
    '---------------------------------------------------------------
    'Do tests with error trapping, printing results on the Form:
    
    Private Sub PerformTests()
        On Error Resume Next
        Print IsEmptyB(B)
        If Err Then Print Err.Number, Err.Description
        Err.Clear
        Print IsEmptyV(V)
        If Err Then Print Err.Number, Err.Description
        On Error GoTo 0
    End Sub
    
    Private Sub Form_Load()
        AutoRedraw = True
    
        'Doesn't work (subscript out of range errors):
        Erase B
        Erase V
        PerformTests
    
        Print
    
        'Works:
        B = MakeEmptyB()
        V = MakeEmptyV()
        PerformTests
    End Sub
    If the arrays you would normally return would have bounds greater than or equal to zero (0) then you can simplify the "tests" by checking for UBound = -1, which is what these approaches (both Byte and Variant arrays) will return.

    As suggested in the comments in the code above, it usually isn't worth writing these functions. Just use the one-line code inline where you need it.


    If there is an equivalent for other array types I haven't found it. Perhaps you know of a trick for Long, Single, UDT, or other types and can post it here.
    A very good and comprehensive discussion how to determine an EMPTY array. I followed all of replies but none of them give confirmed flawless solution.

    My case:
    Code:
    Public Type udtMapPos
      Row1 As Long
      Col1 As Long
      X1 As Long
      Y1 As Long
    End Type
    private MapPos() As udtMapPos
    What I should use to determine empty MapPos ,either dilettante,olaf or wqweto?

    Edited:
    I decided to use vbAccelerator method:
    Code:
    Private Function ArrayCheck(ByRef vArray As Variant) As Boolean
    
    '/* validity test
    
        On Error Resume Next
    
            '/* an array
            If Not IsArray(vArray) Then
                GoTo Handler
                '/* not dimensioned
            ElseIf IsError(UBound(vArray)) Then
                GoTo Handler
                '/* no members
            ElseIf (UBound(vArray) = -1) Then
                GoTo Handler
            End If
            ArrayCheck = True
    
    Handler:
        On Error GoTo 0
    
    End Function
    Last edited by Jonney; Dec 7th, 2014 at 10:27 PM.

  12. #12
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,075

    Re: VB6 - Returning/Detecting Empty Arrays

    The vbAccelerator-stuff is "overly expressive" in the way it is written,
    but not giving any different results from the short(er) IsDimmed-Routine I've posted further above.

    Both routines route VB-ArrayParams through a (VT_)ByRef-Variant-Hull -
    and that works for most of VBs ArrayTypes - but leaving out Arrays of UDTs,
    as long as those UDTs were not defined in a TypeLib or a Public Class of an
    ActiveX-Dll (IRecordInfo is needed).

    wqweto gave an interesting solution in his post #10, with his Variations around
    leaving out the first param of RtlMoveMemory in the Declaration, in conjunction
    with defining a (larger than 8 Bytes) returnvalue for this (normally defined "void") routine.

    This way he achieved a kind of "DeReference-Function with arbitrary length" - and as
    long as MS is not breaking their stdcall ABI on x86-CPUs, this should work nicely -
    for all of VBs ArrayTypes, even those based on normally defined UDTs.

    Olaf

  13. #13
    VB-aholic & Lovin' It LaVolpe's Avatar
    Join Date
    Oct 2007
    Location
    Beside Waldo
    Posts
    19,541

    Re: VB6 - Returning/Detecting Empty Arrays

    Just FYI. This topic is also discussed in the VB FAQ section

    And regarding the "expression too complex" bug mentioned by Olaf in post #6, that is also addressed
    Insomnia is just a byproduct of, "It can't be done"

    Classics Enthusiast? Here's my 1969 Mustang Mach I Fastback. Her sister '67 Coupe has been adopted

    Newbie? Novice? Bored? Spend a few minutes browsing the FAQ section of the forum.
    Read the HitchHiker's Guide to Getting Help on the Forums.
    Here is the list of TAGs you can use to format your posts
    Here are VB6 Help Files online


    {Alpha Image Control} {Memory Leak FAQ} {Unicode Open/Save Dialog} {Resource Image Viewer/Extractor}
    {VB and DPI Tutorial} {Manifest Creator} {UserControl Button Template} {stdPicture Render Usage}

  14. #14
    Frenzied Member
    Join Date
    Jan 2010
    Posts
    1,103

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by Schmidt View Post
    The vbAccelerator-stuff is "overly expressive" in the way it is written,
    but not giving any different results from the short(er) IsDimmed-Routine I've posted further above.

    Both routines route VB-ArrayParams through a (VT_)ByRef-Variant-Hull -
    and that works for most of VBs ArrayTypes - but leaving out Arrays of UDTs,
    as long as those UDTs were not defined in a TypeLib or a Public Class of an
    ActiveX-Dll (IRecordInfo is needed).

    wqweto gave an interesting solution in his post #10, with his Variations around
    leaving out the first param of RtlMoveMemory in the Declaration, in conjunction
    with defining a (larger than 8 Bytes) returnvalue for this (normally defined "void") routine.

    This way he achieved a kind of "DeReference-Function with arbitrary length" - and as
    long as MS is not breaking their stdcall ABI on x86-CPUs, this should work nicely -
    for all of VBs ArrayTypes, even those based on normally defined UDTs.

    Olaf
    Your IsDimmed is OK as well.
    Thank you for pointing out potential risk in other's code.

  15. #15
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,075

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by LaVolpe View Post
    Just FYI. This topic is also discussed in the VB FAQ section

    And regarding the "expression too complex" bug mentioned by Olaf in post #6, that is also addressed
    Seems that in the FAQ-section the "Not Not check" is still regarded as a "good way to approach this",
    with a dubious workaround for the IDE - and the statement, that the "Error will not happen in a compiled App".

    Well, maybe not in the small TestApp the poster has checked, but I remember quite clearly that in a UseNet-
    discussion about a decade ago, we identified the Not Not check as the cause of "Expression too complex"-
    errors, a Developer reported "as happening in a compiled App" - going away as soon as he recompiled with
    a different Array-check.

    So I would still classify the Not Not approach as "not really recommendable"...

    Olaf

  16. #16
    Member Dragokas's Avatar
    Join Date
    Aug 2015
    Location
    Ukraine
    Posts
    732

    Re: VB6 - Returning/Detecting Empty Arrays

    Hi, wqweto!

    Can you remember, what is 'Reserved' field in your PeekType UDT intended for?

    RtlMoveMemory is a void, so I don't see any need.
    Malware analyst, VirusNet developer, HiJackThis+ author || my CodeBank works

  17. #17
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    4,902

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by Dragokas View Post
    Hi, wqweto!

    Can you remember, what is 'Reserved' field in your PeekType UDT intended for?

    RtlMoveMemory is a void, so I don't see any need.
    It has to do with stdcall calling convention -- small UDTs (I think sizeof below 8 bytes) are returned ByVal (in EDX:EAX) while large ones get an extra output param to implement ByRef retval. The dummy `Currency` field enlarges the struct to force the compiler to pass retval struct ByRef.

    RtlMoveMemory signature is (dest, source, size) while in VB source PeekType is declared weirdly as (source, size -> dest). When dest is a large UDT the compiler emits the actual args to fit (dest, source, size) signature.

    cheers.
    </wqw>
    Last edited by wqweto; Jul 16th, 2018 at 09:11 AM.

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

    Re: VB6 - Returning/Detecting Empty Arrays

    Does PeekArray work with unicode string arrays?

    I know this was fixed in Office/VBE7.dll, but I'm pretty sure this is still an issue in VB6.


    I personally use an midl typelib of GetMem4, which has no issues with unicode string arrays.

    Code:
    [entry("GetMem4")]
    HRESULT AryPtr(	[in] SAFEARRAY(void)* Ptr,	[out,retval]	PTR*	Address);

  19. #19
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    4,902

    Re: VB6 - Returning/Detecting Empty Arrays

    @DEXWERX: No, I don't think it does -- you get the address of the temporary ANSI<->Unicode magic happening. Can't think of anything but typelib supported solution for this.

    cheers,
    </wqw>

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

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by wqweto View Post
    @DEXWERX: No, I don't think it does -- you get the address of the temporary ANSI<->Unicode magic happening. Can't think of anything but typelib supported solution for this.

    cheers,
    </wqw>
    Cool.

    In the case of string arrays we can still extract the pointers from a Variant, as Schmidt has shown.
    Or the runtime function RefVarAry / msvbvm60.dll#__vbaRefVarAry

  21. #21
    Member
    Join Date
    Nov 2019
    Posts
    33

    Re: VB6 - Returning/Detecting Empty Arrays

    @wqweto, I am getting a Runtime 13 error at the line "lPtr = Peek(VarPtr(vArray) + 8)" in the GetArrayDimension function from this thread. I am using Excel 2003. (Sub Demo_ArrayDims.)

    Code:
    Public Function GetArrayDimension(vArray As Variant) As Long
        Const VT_BYREF      As Long = &H4000
        Dim lPtr            As Long
        
        If IsArray(vArray) Then
            lPtr = Peek(VarPtr(vArray) + 8)
            If (PeekInt(VarPtr(vArray)) And VT_BYREF) <> 0 Then
                lPtr = Peek(lPtr)
            End If
            If lPtr <> 0 Then
                GetArrayDimension = PeekInt(lPtr)
            End If
        End If
    End Function
    
    Public Function Peek(ByVal lPtr As Long) As Long
        Call CopyMemory(Peek, ByVal lPtr, 4)
    End Function
    
    Public Function PeekInt(ByVal lPtr As Long) As Integer
        Call CopyMemory(PeekInt, ByVal lPtr, 2)
    End Function
    
    Sub Demo_ArrayDims()
    
        Dim Test2DArray As Variant
        Dim Test3DArray() As Long
    
        Debug.Print GetArrayDimension(Array(20, 30, 400))    'Test 1D array
    
        Test2DArray = [{0, 0, 0, 0; "Apple", "Fig", "Orange", "Pear"}]
        Debug.Print GetArrayDimension(Test2DArray)
    
        ReDim Test3DArray(1 To 3, 0 To 1, 1 To 4)
        Debug.Print GetArrayDimension(Test3DArray)
    
    End Sub

  22. #22
    Fanatic Member
    Join Date
    Aug 2016
    Posts
    573

    Re: VB6 - Returning/Detecting Empty Arrays

    some similar discussion on this forums:
    Id 736285
    Id 375341
    Id 231663

  23. #23
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    4,902

    Re: VB6 - Returning/Detecting Empty Arrays

    Quote Originally Posted by Juggler_IN View Post
    @wqweto, I am getting a Runtime 13 error at the line "lPtr = Peek(VarPtr(vArray) + 8)" in the GetArrayDimension function from this thread. I am using Excel 2003. (Sub Demo_ArrayDims.)
    Is this 64-bit version of MS Office?

    For VBA you'll need some more ceremony to make it work both in 64-bit and 32-bit (incl. 32-bit VB6) like this

    Code:
    Option Explicit
    DefObj A-Z
    
    #Const HasPtrSafe = (VBA7 <> 0) Or (TWINBASIC <> 0)
    
    #If HasPtrSafe Then
    Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    #Else
    Private Enum LongPtr
        [_]
    End Enum
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    #End If
    
    Public Function GetArrayDimension(vArray As Variant) As Long
        Const VT_BYREF      As Long = &H4000
        Dim lPtr            As LongPtr
        
        If IsArray(vArray) Then
            lPtr = PeekPtr(VarPtr(vArray) + 8)
            If (PeekInt(VarPtr(vArray)) And VT_BYREF) <> 0 Then
                lPtr = PeekPtr(lPtr)
            End If
            If lPtr <> 0 Then
                GetArrayDimension = PeekInt(lPtr)
            End If
        End If
    End Function
    
    Private Function PeekPtr(ByVal lPtr As LongPtr) As LongPtr
        Call CopyMemory(PeekPtr, ByVal lPtr, LenB(lPtr))
    End Function
    
    Private Function PeekInt(ByVal lPtr As LongPtr) As Integer
        Call CopyMemory(PeekInt, ByVal lPtr, 2)
    End Function
    
    Sub Demo_ArrayDims()
    
        Dim Test2DArray As Variant
        Dim Test3DArray() As Long
    
        Debug.Print GetArrayDimension(Array(20, 30, 400))    'Test 1D array
    
        'Test2DArray = [{0, 0, 0, 0; "Apple", "Fig", "Orange", "Pear"}]
        Debug.Print GetArrayDimension(Test2DArray)
    
        ReDim Test3DArray(1 To 3, 0 To 1, 1 To 4)
        Debug.Print GetArrayDimension(Test3DArray)
    
    End Sub
    cheers,
    </wqw>

  24. #24
    Member
    Join Date
    Nov 2019
    Posts
    33

    Re: VB6 - Returning/Detecting Empty Arrays

    Thanks wqweto;

  25. #25
    Member
    Join Date
    Nov 2019
    Posts
    33

    Re: VB6 - Returning/Detecting Empty Arrays

    Still giving the runtime at lPtr = PeekPtr(VarPtr(vArray) + 8).

  26. #26
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    4,902

    Re: VB6 - Returning/Detecting Empty Arrays

    Try to post a complete code which shows which is failing. The code module I posted above is working in VBA both 64 bit and 32 bit.

    I need complete module in [code] and [/code] tags which can be copy pasted into a module in VBA and when run will "give me the runtime".

    I don't need your exact code you are working on, but a small complete module which shows the problem when run without modification (so I can just copy/paste it from the forum post into VBA module).

    cheers,
    </wqw>

  27. #27
    Member
    Join Date
    Nov 2019
    Posts
    33

    Re: VB6 - Returning/Detecting Empty Arrays

    Okay, I just tried in a new file and it worked.

    So, I will figure out the conflict on my end. Thanks.

  28. #28
    Member Dragokas's Avatar
    Join Date
    Aug 2015
    Location
    Ukraine
    Posts
    732

    Re: VB6 - Returning/Detecting Empty Arrays

    Returning to initial question and these examples:

    - how to get empty array of classes? (empty, however initialized; bounds: 0 to -1) to be able to use in "for each".
    Thanks.
    Malware analyst, VirusNet developer, HiJackThis+ author || my CodeBank works

  29. #29
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    4,902

    Re: VB6 - Returning/Detecting Empty Arrays

    Add an empty Class1 to an empty Std-EXE project and try this in Form1

    Code:
    Option Explicit
    
    Private Declare Function EmptyObjectArray Lib "oleaut32" Alias "SafeArrayCreateVector" (Optional ByVal VarType As VbVarType = vbObject, Optional ByVal Low As Long = 0, Optional ByVal Count As Long = 0) As Object()
    Private Declare Function EmptyClass1Array Lib "oleaut32" Alias "SafeArrayCreateVector" (Optional ByVal VarType As VbVarType = vbObject, Optional ByVal Low As Long = 0, Optional ByVal Count As Long = 0) As Class1()
    
    Private Sub Form_Load()
        Dim arr() As Object
        arr = EmptyObjectArray
        Debug.Print LBound(arr), UBound(arr)
        ReDim Preserve arr(0 To 10)
        Set arr(0) = New Class1
        Debug.Print LBound(arr), UBound(arr)
        
        Dim cls() As Class1
        cls = EmptyClass1Array
        Debug.Print LBound(cls), UBound(cls)
        ReDim Preserve cls(0 To 10)
        Set cls(0) = New Class1
        Debug.Print LBound(cls), UBound(cls)
    End Sub
    Besides Ubound being -1 the second most important feature is being able to ReDim Preserve such empty array.

    cheers,
    </wqw>

  30. #30
    Member Dragokas's Avatar
    Join Date
    Aug 2015
    Location
    Ukraine
    Posts
    732

    Re: VB6 - Returning/Detecting Empty Arrays

    ***, yesterday I tried the same and it didn't work.
    Today I tested it again without even copy your code, and it works
    Perhaps, need to sleep more.
    Thanks for details, wqweto.
    Malware analyst, VirusNet developer, HiJackThis+ author || my CodeBank works

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