Ok, this is an idea I've been playing around with, inspired by some work by Dilettante and The Trick. And much thanks goes out to both of them.
My idea was to use those concepts and create a class that "looks like" an array (of any numeric data type of your choosing). The primary feature this will have that other typical VB6 arrays don't have is that the data is stored in far memory. These arrays can expand past our 2GB (or 4GB with LAA) VB6 limitations. It's a single class module that you can include into any project. Furthermore, you can instantiate it as many times as you like to create as many far memory arrays as you like.
Furthermore, because this is in far memory, you can actually use it as a way to communicate across processes (so long as you know the "name" of the memory file that you're using). See documentation in the class for more information on this. And, just as an FYI, these far memory files hang around so long as one process has a file handle opened against it. When the last handle is closed, the file is purged from far memory.
Also, don't let the nomenclature of "file" confuse you. These are memory files, not disk based files, other than the possibility that the data may get pushed into the OS's paging virtual memory if you ask for more memory than is available in your computer. And, if this happens, these things will perform much slower than when this doesn't happen.
One CAVEAT about these things. When developing in the IDE, it's not the best idea to use the "Stop" button when you've got one (or more) copies of the MemoryBasedArray.cls array instantiated. The reason is, once you call the Initialization procedure within that class, you have a far memory file open. And it's the Class_Terminate event that closes that file. If you don't explicitly close it, even when returning to IDE development mode, that file will stay open. There's no great harm in this, and it won't crash the IDE. However, the next time you execute your program, you will probably get a "File Already Open" error. And then, the only way to clear that error is to close the IDE and re-open it.
What types of arrays will this thing store? It will store any of the VB6 intrinsic types: vbByte, vbBoolean, vbInteger, vbLong, vbSingle, vbCurrency, vbDate, vbDouble, & vbDecimal.
Notice that even vbDecimal is included in that list. The entire Variant (holding a Decimal) is stored in that case, all 16 bytes.
There is also a vbString option/specification. These aren't exactly BSTR strings nor fixed-length-strings. They're better thought of as similar to fixed database fields specified to hold Unicode strings. Also, there are some criteria for these things ... primarily that they can't have vbNullChar values in the trailing characters of the string. The vbNullChar is used for padding within the buffer. And, when these strings are returned, they're right-trimmed for vbNullChar. So long as the trailing character of an input string isn't vbNullChar, they can contain other vbNullChar values with no problem.
Also, the Value (both Let & Get) property of this class is the default, so, once instantiated and initialized, you can use it like a true array (with the index and value).
There is a "test" project attached. I've also shown the code of the class, but you're better off to get the class out of the test project. As, that way, the Value property will stay the default property.
---------------
Also, in the thread where I was initially developing this, there was some discussion of putting UDTs into these things. With the use of these helper procedures, you could do that. However, there are a couple of caveats. As stated above, these fixed length strings must be an integer divisor of the system's granularity, which is some power of 2. So, you may need to round up to such a number when specifying iFixedStringCharLen in the Initialization.
Also, as stated above, using those fixed length strings with this, you can't pass in strings with any trailing vbNullChar values. Having a string with a trailing vbNullChar would be easy to do if the last item in the UDT was a number with a value of zero. So, you may need to append some non-zero value (possibly just any character) to the end of the resulting string (from the UDT) to avoid this.
---------------
I've now tested in many ways, but here's the test code in the attached Form1. I've tested both the fixed length strings and the decimal type (both a bit unusual).
Notice I've put in some Stop commands, just so you can see what's going on. Again, be careful to not use the Stop "button" too much with this stuff, as you'll be reloading your IDE if you do, to clear the "File Already Open" error.
---------------
I look forward to any discussion anyone might like to have about this stuff.
My idea was to use those concepts and create a class that "looks like" an array (of any numeric data type of your choosing). The primary feature this will have that other typical VB6 arrays don't have is that the data is stored in far memory. These arrays can expand past our 2GB (or 4GB with LAA) VB6 limitations. It's a single class module that you can include into any project. Furthermore, you can instantiate it as many times as you like to create as many far memory arrays as you like.
Furthermore, because this is in far memory, you can actually use it as a way to communicate across processes (so long as you know the "name" of the memory file that you're using). See documentation in the class for more information on this. And, just as an FYI, these far memory files hang around so long as one process has a file handle opened against it. When the last handle is closed, the file is purged from far memory.
Also, don't let the nomenclature of "file" confuse you. These are memory files, not disk based files, other than the possibility that the data may get pushed into the OS's paging virtual memory if you ask for more memory than is available in your computer. And, if this happens, these things will perform much slower than when this doesn't happen.
One CAVEAT about these things. When developing in the IDE, it's not the best idea to use the "Stop" button when you've got one (or more) copies of the MemoryBasedArray.cls array instantiated. The reason is, once you call the Initialization procedure within that class, you have a far memory file open. And it's the Class_Terminate event that closes that file. If you don't explicitly close it, even when returning to IDE development mode, that file will stay open. There's no great harm in this, and it won't crash the IDE. However, the next time you execute your program, you will probably get a "File Already Open" error. And then, the only way to clear that error is to close the IDE and re-open it.
What types of arrays will this thing store? It will store any of the VB6 intrinsic types: vbByte, vbBoolean, vbInteger, vbLong, vbSingle, vbCurrency, vbDate, vbDouble, & vbDecimal.
Notice that even vbDecimal is included in that list. The entire Variant (holding a Decimal) is stored in that case, all 16 bytes.
There is also a vbString option/specification. These aren't exactly BSTR strings nor fixed-length-strings. They're better thought of as similar to fixed database fields specified to hold Unicode strings. Also, there are some criteria for these things ... primarily that they can't have vbNullChar values in the trailing characters of the string. The vbNullChar is used for padding within the buffer. And, when these strings are returned, they're right-trimmed for vbNullChar. So long as the trailing character of an input string isn't vbNullChar, they can contain other vbNullChar values with no problem.
Also, the Value (both Let & Get) property of this class is the default, so, once instantiated and initialized, you can use it like a true array (with the index and value).
There is a "test" project attached. I've also shown the code of the class, but you're better off to get the class out of the test project. As, that way, the Value property will stay the default property.
Code:
' Ideas herein were inspired by some work that Dilettante & The Trick (vbforums.com) have done.
'
' With this class, you can create an array that uses "far" memory,
' and isn't limited to the 2GB (or 4GB with LAA) that VB6 is limited to.
'
' Initialize must be called immediately after instantiation.
' Then, the Value property (Get & Let) can be used.
'
Option Explicit
'
Private Type SYSTEM_INFO
Reserved1(27&) As Byte
dwAllocationGranularity As Long ' For purposes herein, this is all we need.
Reserved2(3&) As Byte
End Type
'
Private Declare Function CreateFileMapping Lib "kernel32" Alias "CreateFileMappingA" (ByVal hFile As Long, ByVal lpFileMappigAttributes As Long, ByVal flProtect As Long, ByVal dwMaximumSizeHigh As Long, ByVal dwMaximumSizeLow As Long, ByVal lpName As String) As Long
Private Declare Function MapViewOfFile Lib "kernel32" (ByVal hFileMappingObject As Long, ByVal dwDesiredAccess As Long, ByVal dwFileOffsetHigh As Long, ByVal dwFileOffsetLow As Long, ByVal dwNumberOfBytesToMap As Long) As Long
Private Declare Function OpenFileMapping Lib "kernel32" Alias "OpenFileMappingA" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal lpName As String) As Long
Private Declare Function UnmapViewOfFile Lib "kernel32" (ByVal lpBaseAddress As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
'
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (ByRef Destination As Long, ByRef Source As Long, ByVal Length As Long)
Private Declare Sub ZeroMemory Lib "kernel32" Alias "RtlZeroMemory" (ByRef Destination As Long, ByVal Length As Long)
Private Declare Sub GetSystemInfo Lib "kernel32" (ByRef lpSystemInfo As SYSTEM_INFO)
Private Declare Function VariantChangeType Lib "oleaut32" (Dest As Variant, src As Variant, ByVal wFlags As Integer, ByVal vt As Long) As Long
'
Private mbInit As Boolean
Private mhMemFile As Long
Private miVarType As Long
Private miItemBytes As Long
Private mvMaxCount As Variant ' Decimal.
Private miVariantOffset As Long
Private miGranularity As Long
'
Private mpMapView As Long
Private mdwViewHigh As Long
Private mdwViewLow As Long
'
Public Sub Initialize(ByRef sUniqueName As String, iVarType As VBA.VbVarType, iMaxItemCount As Variant, Optional iFixedStringCharLen As Long = 10&, Optional bOpenOnlyNoCreate As Boolean = False)
'
' sUniqueName is a system-wide thing. If other programs are using CreateFileMapping,
' the sUniqueName must be unique with respect to those, and not only names used within this project.
'
' iVarType is simply the variable type you'll be storing in this array.
' Or, fixed length strings (not the same as VB6's fixed length strings) are allowed.
'
' iMaxItemCount is the maximum (not necessily used) number of items in the array.
' You will get an error if you overflow this when using the Value properties.
' Note that far memory is allocated based on this iMaxItemCount argument.
' This iMaxItemCount must be a numeric integer. It's not a Long so that even more than a Long's limits can be used.
'
' If iVarType = vbString then iFixedStringCharLen is examined for how long they should be.
' As a note, these strings CAN'T end in vbNullChar, as that's reserved for padding in these things.
' Also, their length must an integer divisor of the system's granularity (typically some power of 2).
'
If mbInit Then Exit Sub ' Only allow this to be called once.
If Not IsNumeric(iMaxItemCount) Then Err.Raise 13&, TypeName(Me), "iMaxItemCount must be numeric."
If iMaxItemCount < 1& Then Err.Raise 5&, TypeName(Me), "Count must be at least 1."
'
' Save granularity.
miGranularity = MemAllocGranularity
'
' The only allowed types are: vbBoolean, vbByte, vbCurrency, vbDate, vbDecimal, vbDouble, vbInteger, vbLong, vbSingle, or vbString.
Select Case iVarType
Case vbByte: miItemBytes = 1&: miVariantOffset = 8& ' These are the length (bytes) and offset with a variant for our data types.
Case vbBoolean, vbInteger: miItemBytes = 2&: miVariantOffset = 8& ' In most cases (all but Decimal), a variant stores data at an 8 byte offset.
Case vbLong, vbSingle: miItemBytes = 4&: miVariantOffset = 8&
Case vbCurrency, vbDate, vbDouble: miItemBytes = 8&: miVariantOffset = 8&
Case vbDecimal: miItemBytes = 16&: miVariantOffset = 0& ' This is the one case where all 14 bytes of the variant's data are used.
Case vbString
' This one needs a bit of special handling.
miItemBytes = iFixedStringCharLen * 2& ' Unicode.
Select Case True
Case miGranularity < miItemBytes
Err.Raise 6&, TypeName(Me), "Fixed string length (" & CStr(iFixedStringCharLen) & ") overflow. They can't be longer than the system's granularity / 2 (" & CStr(miGranularity / 2) & ")."
Case iFixedStringCharLen < 1&
Err.Raise 6&, TypeName(Me), "Fixed string length underflow. Length: " & CStr(iFixedStringCharLen)
Case miGranularity Mod miItemBytes <> 0
Err.Raise 6&, TypeName(Me), "Fixed string length * 2 (for Unicode) (" & CStr(iFixedStringCharLen) & ") not an even divisor of the system's granularity (" & CStr(miGranularity) & ")."
End Select
'
miVariantOffset = 8& ' But, in this case, it's the BSTR pointer.
Case Else: Err.Raise 13&, TypeName(Me), "Invalid variable type specified."
End Select
'
' Save our initialization properties.
miVarType = iVarType
mvMaxCount = CDec(iMaxItemCount)
'
' Figure out byte size of Mapped File, and round UP to a multiple of MemAllocGranularity.
Dim vTotalBytes As Variant
vTotalBytes = CDec(miItemBytes) * mvMaxCount
vTotalBytes = Int((vTotalBytes - CDec(1&) + CDec(miGranularity)) / CDec(miGranularity)) * CDec(miGranularity)
'
' Copy low and high into MapViewOfFile offset arguments.
Dim dwMaximumSizeHigh As Long
Dim dwMaximumSizeLow As Long
'
' Variant structure with a Decimal.
' VariantType As Integer ' Reserved, to act as the Variant Type when sitting in a 16-Byte-Variant. Equals vbDecimal(14) when it's a Decimal type.
' Base10NegExp As Byte ' Base 10 exponent (0 to 28), moving decimal to right (smaller numbers) as this value goes higher. Top three bits are never used.
' sign As Byte ' Sign bit only. Other bits aren't used.
' Hi32 As Long ' Mantissa.
' Lo32 As Long ' Mantissa.
' Mid32 As Long ' Mantissa.
CopyMemory dwMaximumSizeHigh, ByVal PtrAdd(VarPtr(vTotalBytes), 12&), 4& ' Mid32
CopyMemory dwMaximumSizeLow, ByVal PtrAdd(VarPtr(vTotalBytes), 8&), 4& ' Lo32
'
' Create our memory file.
Const INVALID_HANDLE_VALUE As Long = -1&
Const PAGE_READWRITE As Long = 4&
Const FILE_MAP_WRITE As Long = 2&
Const FILE_MAP_READ As Long = 4&
'
If Not bOpenOnlyNoCreate Then
mhMemFile = CreateFileMapping(INVALID_HANDLE_VALUE, 0&, PAGE_READWRITE, dwMaximumSizeHigh, dwMaximumSizeLow, sUniqueName)
If mhMemFile = 0& Then
If Err.LastDllError = 1450& Then
Err.Raise Err.LastDllError, TypeName(Me), "CreateFileMapping error ERROR_NO_SYSTEM_RESOURCES. This probably means you don't have enough memory in this computer to map file(s) as large as you're trying to, or maybe memory is full with other executing programs."
Else
Err.Raise Err.LastDllError, TypeName(Me), "CreateFileMapping API system error."
End If
End If
'
Const ERROR_ALREADY_EXISTS As Long = 183&
If Err.LastDllError = ERROR_ALREADY_EXISTS Then CloseMemFile: Err.Raise 55&, TypeName(Me), sUniqueName & " already open."
Else
mhMemFile = OpenFileMapping(FILE_MAP_READ + FILE_MAP_WRITE, 0&, sUniqueName)
If mhMemFile = 0& Then Err.Raise Err.LastDllError, TypeName(Me), "OpenFileMapping API system error. Make sure the file exists."
End If
'
' All done and ready to be used.
mbInit = True
End Sub
Private Sub Class_Terminate()
' When all handles to the mapped object are closed, it disappears.
' When in the IDE, abnormal termination can leave the file open,
' and only way to get rid of it is to restart the IDE.
' When compiled, it's not a problem.
'
CloseMemFile
End Sub
Private Sub CloseMemFile()
If mpMapView Then
ApiZ UnmapViewOfFile(mpMapView)
mpMapView = 0&
End If
If mhMemFile Then
ApiZ CloseHandle(mhMemFile)
mhMemFile = 0&
End If
End Sub
Public Property Let Value(index As Variant, vValue As Variant)
' Zero based index. It can be any numeric value, but will always be treated as an integer,
' and internally, it'll be handled as a Decimal.
'
' If you need an index larger than 2147483647 (&h7fffffff), you can cast a string to a decimal
' using something like: CDec("99999999999"), or just use Decimal types in the first place for your indices.
'
If Not mbInit Then Exit Property
'
' Make sure we've got valid arguments.
If VarType(vValue) <> miVarType Then CloseMemFile: Err.Raise 13&, TypeName(Me), "Value type doesn't match initialization type: " & TypeName(vValue)
Dim vDecIdx As Variant
vDecIdx = ValidateIndex(index)
'
' Create a map view of our memory file.
Dim iGranOffset As Long
iGranOffset = CreateSingleItemMapping(vDecIdx)
'
' Put data into memory mapped file.
If miVarType <> vbString Then
CopyMemory ByVal PtrAdd(mpMapView, iGranOffset), ByVal PtrAdd(VarPtr(vValue), miVariantOffset), miItemBytes
Else
ZeroMemory ByVal PtrAdd(mpMapView, iGranOffset), miItemBytes
Dim iChars As Long
iChars = miItemBytes \ 2&
Dim s As String
s = String$(iChars, vbNullChar) ' Create a buffer.
Mid$(s, 1&, Len(vValue)) = vValue ' s is now padded with vbNullChar if necessary.
CopyMemory ByVal PtrAdd(mpMapView, iGranOffset), ByVal StrPtr(s), miItemBytes ' We ignore the BSTR zero terminator.
End If
End Property
Public Property Get Value(index As Variant) As Variant
' Zero based index. See notes in "Let Value" property.
'
If Not mbInit Then Exit Property
'
' Make sure we've got valid arguments.
Dim vDecIdx As Variant
vDecIdx = ValidateIndex(index)
'
' Create a map view of our memory file.
Dim iGranOffset As Long
iGranOffset = CreateSingleItemMapping(vDecIdx)
'
' Get data from memory mapped file.
If miVarType <> vbString Then
Value = CLng(0&)
If miVarType <> vbLong Then ApiE VariantChangeType(Value, Value, 0&, miVarType), "VariantChangeType" ' Make our variant the correct type.
CopyMemory ByVal PtrAdd(VarPtr(Value), miVariantOffset), ByVal PtrAdd(mpMapView, iGranOffset), miItemBytes
Else ' Handle strings.
Dim iChars As Long
iChars = miItemBytes \ 2&
Dim ia() As Integer
ReDim ia(1& To iChars) ' Create a buffer.
CopyMemory ByVal VarPtr(ia(1&)), ByVal PtrAdd(mpMapView, iGranOffset), miItemBytes
' Need to trim null characters (from end).
Dim i As Long
For i = UBound(ia) To 1& Step -1&
If ia(i) Then Exit For ' We found something non-zero.
Next
If i Then ' If it wound down to 0, then it was all zeroes.
Dim s As String
s = Space$(i)
CopyMemory ByVal StrPtr(s), ByVal VarPtr(ia(1&)), i * 2& ' Unicode.
Value = s
Else
Value = vbNullString
End If
End If
End Property
Private Function ValidateIndex(index As Variant) As Variant ' vDecIdx is returned.
If Not IsNumeric(index) Then CloseMemFile: Err.Raise 9&, TypeName(Me), "Bad index type: " & TypeName(index)
Dim vDecIdx As Variant
vDecIdx = CDec(index)
If vDecIdx < 0& Or (vDecIdx + 1&) > mvMaxCount Then CloseMemFile: Err.Raise 9&, TypeName(Me), "Bad index range: " & CStr(vDecIdx)
If vDecIdx <> Int(vDecIdx) Then CloseMemFile: Err.Raise 9&, TypeName(Me), "Bad index value: " & CStr(vDecIdx)
'
ValidateIndex = vDecIdx
End Function
Private Function CreateSingleItemMapping(ByVal vDecIdx As Variant) As Long
' The iGranOffset is returned, which is an offset in the "View" to the specific item requested.
' mpMapView is also set.
'
' Convert vDecIdx into a byte offset.
vDecIdx = vDecIdx * CDec(miItemBytes)
'
' Calculate an offset that appreciates granularity.
Dim vTemp As Variant
vTemp = Int(vDecIdx / CDec(miGranularity)) ' Rounds down, preserving Decimal type.
vTemp = vTemp * CDec(miGranularity) ' This can now be used in MapViewOfFile API call.
CreateSingleItemMapping = vDecIdx - vTemp ' This provides an offset for addressing a single item.
'
' Copy low and high into MapViewOfFile offset arguments.
Dim dwFileOffsetHigh As Long
Dim dwFileOffsetLow As Long
'
' Variant structure with a Decimal.
' VariantType As Integer ' Reserved, to act as the Variant Type when sitting in a 16-Byte-Variant. Equals vbDecimal(14) when it's a Decimal type.
' Base10NegExp As Byte ' Base 10 exponent (0 to 28), moving decimal to right (smaller numbers) as this value goes higher. Top three bits are never used.
' sign As Byte ' Sign bit only. Other bits aren't used.
' Hi32 As Long ' Mantissa.
' Lo32 As Long ' Mantissa.
' Mid32 As Long ' Mantissa.
CopyMemory dwFileOffsetHigh, ByVal PtrAdd(VarPtr(vTemp), 12&), 4& ' Mid32
CopyMemory dwFileOffsetLow, ByVal PtrAdd(VarPtr(vTemp), 8&), 4& ' Lo32
'
' Make sure we need to do something.
If mpMapView = 0& Or mdwViewHigh <> dwFileOffsetHigh Or mdwViewLow <> dwFileOffsetLow Then
If mpMapView Then ApiZ UnmapViewOfFile(mpMapView)
mdwViewHigh = 0&
mdwViewLow = 0&
'
' Create a mapview of our memory file.
Const FILE_MAP_WRITE = 2&
Const FILE_MAP_READ = 4&
mpMapView = MapViewOfFile(mhMemFile, FILE_MAP_READ + FILE_MAP_WRITE, dwFileOffsetHigh, dwFileOffsetLow, miGranularity)
If mpMapView = 0& Then CloseMemFile: Err.Raise Err.LastDllError, TypeName(Me), "MapViewOfFile system error."
'
mdwViewHigh = dwFileOffsetHigh
mdwViewLow = dwFileOffsetLow
End If
End Function
Private Function MemAllocGranularity() As Long
' When using MapViewOfFile, the quad_word offset must be a multiple of this granularity (per MSDN).
Dim si As SYSTEM_INFO
GetSystemInfo si
MemAllocGranularity = si.dwAllocationGranularity
End Function
Private Function PtrAdd(ByVal Ptr As Long, ByVal iOffset As Long) As Long
' For adding (or subtracting) a small number from a pointer.
PtrAdd = (Ptr Xor &H80000000) + iOffset Xor &H80000000
End Function
Private Function ApiZ(ApiReturn As Long, Optional sApiCall As String) As Long
' This one is for API calls that report error by returning ZERO.
'
If ApiReturn <> 0& Then
ApiZ = ApiReturn
Exit Function
End If
'
Dim sErr As String
If Len(sApiCall) Then
sErr = sApiCall & " error " & CStr(Err.LastDllError)
Else
sErr = "API Error " & CStr(Err.LastDllError)
End If
'
Dim InIDE As Boolean: Debug.Assert MakeTrue(InIDE)
If InIDE Then
Debug.Print sErr
Stop
Else
Err.Raise vbObjectError + 1147221504, TypeName(Me), sErr
End If
End Function
Private Sub ApiE(ApiReturn As Long, Optional sApiCall As String)
' Just a general error processing procedure for API errors.
' For API calls where 0& is OK.
'
If ApiReturn = 0& Then Exit Sub
'
Dim sErr As String
If Len(sApiCall) Then
sErr = sApiCall & " error " & CStr(ApiReturn)
Else
sErr = "API Error " & CStr(ApiReturn)
End If
'
Dim InIDE As Boolean: Debug.Assert MakeTrue(InIDE)
If InIDE Then
Debug.Print sErr
Stop
Else
Err.Raise vbObjectError + 1147221504 - ApiReturn, TypeName(Me), sErr
End If
End Sub
Private Function MakeTrue(ByRef b As Boolean) As Boolean
b = True
MakeTrue = True
End Function
Also, in the thread where I was initially developing this, there was some discussion of putting UDTs into these things. With the use of these helper procedures, you could do that. However, there are a couple of caveats. As stated above, these fixed length strings must be an integer divisor of the system's granularity, which is some power of 2. So, you may need to round up to such a number when specifying iFixedStringCharLen in the Initialization.
Also, as stated above, using those fixed length strings with this, you can't pass in strings with any trailing vbNullChar values. Having a string with a trailing vbNullChar would be easy to do if the last item in the UDT was a number with a value of zero. So, you may need to append some non-zero value (possibly just any character) to the end of the resulting string (from the UDT) to avoid this.
---------------
I've now tested in many ways, but here's the test code in the attached Form1. I've tested both the fixed length strings and the decimal type (both a bit unusual).
Code:
Option Explicit
'
Private Sub Form_Load()
Debug.Print
Debug.Print "********************************"
Debug.Print "String array test:"
Dim oStr As ArraysInFarMemory
Set oStr = New ArraysInFarMemory
oStr.Initialize "StrTest", vbString, 700000, 256&
'
oStr(0&) = "aaaa" ' Illustrating default property.
oStr.Value(1&) = "bbbbbbbbbbbb" ' Too long so it'll be truncated.
oStr.Value(2&) = vbNullString
oStr(300000) = "dddddddd" ' Illustrating default property.
Debug.Print "'"; oStr.Value(0&); "'"; " should be 'aaaa'"
Debug.Print "'"; oStr(1&); "'"; " should be 'bbbbbbbbbbbb'" ' Illustrates default property.
Debug.Print "'"; oStr.Value(2&); "'"; " should be empty"
Debug.Print "'"; oStr.Value(3&); "'"; " should be empty"
Debug.Print "'"; oStr.Value(4&); "'"; " should be empty"
Dim c As Long
For c = 1& To 500000
oStr(c) = CStr(c)
If oStr(c) <> CStr(c) Then Debug.Print "bad put/get": Stop
If c Mod 50000 = 0& Then Debug.Print CStr(c)
Next
Set oStr = Nothing
Debug.Print "Successfully stored and retrieved 500,000 string values,"
Debug.Print "verifying that they were stored correctly."
Debug.Print
Stop
Debug.Print
Debug.Print "********************************"
Debug.Print "Decimal array test:"
' We'll use the default property of the class for all of this work.
Dim oDec As ArraysInFarMemory
Set oDec = New ArraysInFarMemory
oDec.Initialize "DecimalTest", vbDecimal, 500000
oDec(0&) = CDec("987654321987654321987654321") ' Decimals can hold REALLY big numbers.
oDec(400000) = CDec("999888")
Debug.Print oDec(0&); " should be 987654321987654321987654321"
Debug.Print oDec(400000); " should be 999888"
Dim d As Long
For d = 0& To 490000
oDec(d) = CDec(d)
If oDec(d) <> CDec(d) Then Debug.Print "bad put/get": Stop
If d Mod 50000 = 0& Then Debug.Print CDec(d)
Next
Set oDec = Nothing
Debug.Print "Successfully stored and retrieved 490,000 decimal values,"
Debug.Print "verifying that they were stored correctly."
Debug.Print
Stop
Unload Me
End Sub
Notice I've put in some Stop commands, just so you can see what's going on. Again, be careful to not use the Stop "button" too much with this stuff, as you'll be reloading your IDE if you do, to clear the "File Already Open" error.
---------------
I look forward to any discussion anyone might like to have about this stuff.