-
Sep 28th, 2013, 10:16 AM
#1
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
-
Sep 28th, 2013, 03:18 PM
#2
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
-
Sep 28th, 2013, 04:38 PM
#3
Re: VB6 - Returning/Detecting Empty Arrays
Good catch, I'll change that.
Thanks for the String array trick, another useful one!
-
Oct 6th, 2013, 02:01 PM
#4
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.
-
Oct 18th, 2013, 03:08 AM
#5
New Member
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by dilettante
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)
-
Oct 18th, 2013, 04:15 AM
#6
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.
-
Oct 18th, 2013, 05:58 AM
#7
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by Schmidt
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.
-
Oct 20th, 2013, 09:52 AM
#8
Hyperactive Member
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.
-
Oct 20th, 2013, 01:01 PM
#9
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by k_zeon
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
-
Oct 26th, 2013, 12:57 PM
#10
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>
-
Dec 7th, 2014, 09:45 PM
#11
Frenzied Member
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by dilettante
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.
-
Dec 7th, 2014, 11:55 PM
#12
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
-
Dec 8th, 2014, 12:01 AM
#13
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
-
Dec 8th, 2014, 12:37 AM
#14
Frenzied Member
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by Schmidt
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.
-
Dec 8th, 2014, 12:40 AM
#15
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by LaVolpe
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
-
May 14th, 2017, 07:37 PM
#16
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.
-
May 15th, 2017, 02:58 AM
#17
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by Dragokas
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.
-
May 15th, 2017, 10:21 AM
#18
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);
-
May 15th, 2017, 10:34 AM
#19
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>
-
May 15th, 2017, 11:28 AM
#20
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by wqweto
@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
-
Jul 22nd, 2022, 02:56 AM
#21
Member
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
-
Jul 22nd, 2022, 03:23 AM
#22
Fanatic Member
Re: VB6 - Returning/Detecting Empty Arrays
some similar discussion on this forums:
Id 736285
Id 375341
Id 231663
-
Jul 22nd, 2022, 04:30 AM
#23
Re: VB6 - Returning/Detecting Empty Arrays
 Originally Posted by Juggler_IN
@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>
Last edited by wqweto; Jul 22nd, 2022 at 04:33 AM.
-
Jul 28th, 2022, 03:14 AM
#24
Member
Re: VB6 - Returning/Detecting Empty Arrays
-
Jul 28th, 2022, 03:29 AM
#25
Member
Re: VB6 - Returning/Detecting Empty Arrays
Still giving the runtime at lPtr = PeekPtr(VarPtr(vArray) + 8).
-
Jul 28th, 2022, 05:29 AM
#26
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>
-
Jul 28th, 2022, 05:55 AM
#27
Member
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.
-
Sep 22nd, 2023, 05:34 PM
#28
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.
-
Sep 23rd, 2023, 06:21 AM
#29
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>
-
Sep 23rd, 2023, 06:47 AM
#30
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.
Posting Permissions
- You may not post new threads
- You may not post replies
- You may not post attachments
- You may not edit your posts
-
Forum Rules
|
Click Here to Expand Forum to Full Width
|