« StringList Class | Main| The Black Knight Returns »

StringListBig Class

QuickImage Category Technical

If you took a look at yesterday's post on the StringList Class, you might be asking yourself why even bother with this class, considering that LotusScript has the very cool built in List object. Given the choice, I would personally prefer to use the List object myself (and I normally do).

However, I created this class due to a need found when attempting to port some LotusScript code to Visual Basic, which doesn't have a List class. Did I mention lately that Visual Basic Sucks? (Ok, it really doens't suck that bad, but the Visual Studio IDE.....better stop myself from going into rant mode, need to keep that blood pressure under control..)

Anyway, back to the task at hand. After I created this class, I realized that it was a perfect foundation for something that has been swimming around in the back of my mind for a while; a big array. Or, in this case, a big string list.

The LotusScript List class and LotusScript arrays are theoretically limited to 65,536 elements (range of integer, -32,768 to 32,767). The actual number of usable elements is constrained a bit by other factors. From the notes help:

...Determined by memory available for data, and by the storage size of each element of the array, which varies with the array data type. For example, a Long one-dimensional fixed array declared in type scope can have 16,128 elements. (The total storage size available for fixed-size data in module scope is 64K bytes, and a Long element requires 4 bytes for storage.)

While this seems like a lot of entries, there have been times where I have come close to needing more. So far, I have been able to find other ways to handle this, but there are always possibilities. That being said, I have created the next "evolution" of the StringList class. This is the StringListBig class. It is essentially nothing more than a 256 (byte range) element array StringLists (which is itself a 256 element array of strings) with some wrapper functionality tacked on. This gives a real (not just theoretical) maximum potential size of 65,536 (256 * 256) elements. Enjoy the code:

' Option Public INTENTIONALLY REMOVED
Option Explicit
Use "class_StringList"

Public Class StringListBig

%REM
This class is a 256 element array of StringLists.
The properties and methods allow easy navigation of the array.
Externally, this class acts like StringList with 65536 possible elements.
This is accomplished because each element in this class is itself a 256 element array.
256 * 256 = 65536
%END REM

Private bool_Initialized As
Boolean
Private byteCurrentPos As Byte
Private byteUbound As Byte
Private lngElements As Long
Private varElements() As StringList
Private MAX_ELEMENTS As Long ' Set in Initialize_Class to 65536, then treated as a constant

' INTERFACE
' PROPERTIES
Public Property Get HasElements As Boolean
 HasElements =
(lngElements& > 0)
End Property ' Get HasElements

Public Property Get ElementCount As Long
 ElementCount =
lngElements
End Property ' Get ElementCount

Public Property Get MaxElements As Long
 MaxElements =
MAX_ELEMENTS
End Property ' MaxElements

' METHODS
Public Sub New
 Call
Initialize_Class
End Sub ' New

Public Sub Initialize_Class
 If
bool_Initialized Then
  For byteCurrentPos = 0 To byteUbound
   Delete varElements(byteCurrentPos)
  Next ' byteCurrentPos
 End If ' bool_Initialized
 
 byteCurrentPos = 0
 byteUbound = 0
 lngElements = 0
 Redim varElements(0) As StringList
 Set varElements(0) = New StringList
 MAX_ELEMENTS = 65536 ' 256 * 256
 bool_Initialized = True
End Sub ' Initialize_Class

Public Function AddElement (strSource As String) As Boolean
 ' Returns True if the element is added to the StringListBig, returns False otherwise.
 
 On Error Goto ErrorTrap
 
 If (lngElements < MAX_ELEMENTS) Then
  If (varElements(byteUbound).ElementCount >= 256) Then
   incValue byteUbound, 1
   Redim Preserve varElements(byteUbound) As StringList
   Set varElements(byteUbound) = New StringList
  End If ' (varElements(byteUbound).ElementCount >= 256)
 
  If varElements(byteUbound).AddElement(strSource) Then
   incValue lngElements, 1
   byteCurrentPos = byteUbound
   AddElement = True
  Else
   AddElement = False
  End If ' varElements(byteUbound).AddElement(strSource)
 Else
  AddElement = False
 End If ' (lngElements < MAX_ELEMENTS)
 
ExitPoint:
 Exit Function
ErrorTrap:
 AddElement = False
 Messagebox Error(), 16, "Error # " & Cstr(Err())
 Resume ExitPoint
End Function ' AddElement

Public Function GetFirst As String
 
' returns the first element of the StringListBig
 GetFirst =
varElements(0).GetFirst
 byteCurrentPos = 0
End Function ' GetFirst

Public Function GetNext As String
 
' returns the next elment (based on the current position) of the StringListBig
 
 If
(varElements(byteCurrentPos).CurrentElementNumber < 256) Then
  GetNext = varElements(byteCurrentPos).GetNext
 Else
  ' The end of the current StringList element has been reached,
  ' check if there are more elements in the BigStringList
  If (byteCurrentPos < byteUbound) Then
   ' there are more elements
   ' change to the next element, and return the element's first entry
   incValue byteCurrentPos, 1
   GetNext = varElements(byteCurrentPos).GetFirst
  Else
   ' there are no more elements. return a blank string
   GetNext = ""
  End If ' (byteCurrentPos < byteUbound)
 End If ' (varElements(byteCurrentPos)...
End Function ' GetNext

Public Function GetPrevious As String
 
' returns the previous elment (based on the current position) of the StringListBig
 If
(varElements(byteCurrentPos).CurrentElementNumber > 1) Then
  GetPrevious = varElements(byteCurrentPos).GetPrevious
 Else
  ' The beginning of the current StringList element has been reached,
  ' check if there are previous elements in the BigStringList
  If (byteCurrentPos > 0) Then
   ' there are previous elements
   ' change to the previous element, and return the element's last entry
   incValue byteCurrentPos, -1
   GetPrevious = varElements(byteCurrentPos).GetLast
  Else
   ' there are no previous elements. return a blank string
   GetPrevious = ""
  End If ' (byteCurrentPos > 0)
 End If ' (varElements(byteCurrentPos)...
End Function ' GetPrevious

Public Function GetLast As String
 
' returns the last element of the StringListBig
 GetLast =
varElements(byteUbound).GetLast
 byteCurrentPos = byteUbound
End Function ' GetLast

Public Function OrdEntry (lngPos As Long) As String
 ' returns the entry at the psuedo ordinal position
 
 Dim byteInnerPos As Byte
 
 If Me.HasElements Then
  If (lngPos < lngElements) Then
   If (lngPos < 256) Then
    OrdEntry = varElements(0).OrdEntry(Cbyte(lngPos))
   Else
    byteCurrentPos = Cbyte(lngPos \ 255) ' INTEGER DIVISION
    byteInnerPos = Cbyte(lngPos Mod 255) ' REMAINDER ONLY
    OrdEntry = varElements(byteCurrentPos).OrdEntry(byteInnerPos)
   End If ' (lngPos < 256)
  Else
   OrdEntry = ""
  End If ' (lngPos < lngElements)
 Else
  OrdEntry = ""
 End If ' Me.HasElements
End Function ' OrdEntry

Public Function PopLast As String
 
' This function is similar to GetLast,
 
' except it also removes the last element from the StringListBig
 If
(lngElements > 0) Then
 
  incValue lngElements, -1
 
  PopLast = varElements(byteUbound).PopLast
 
  If (varElements(byteUbound).ElementCount < 1) Then
  ' The current StringList element has no more elements.
  ' Check if there are previous StringList Elements.
   If (byteUbound > 0) Then
   ' There are previous StringList Elements.
   ' Remove the last StringList Element.
    Delete varElements(byteUbound)
    incValue byteUbound, -1
    Redim Preserve varElements(byteUbound)
    byteCurrentPos =
byteUbound
   End If ' (byteUbound > 0)
  End If ' (varElements(byteUbound).ElementCount < 1)
 Else
  PopLast = ""
 End If ' (lngElements > 0)
End Function ' PopLast

Public Sub Delete
 If
bool_Initialized Then
  For byteCurrentPos = 0 To byteUbound
   Delete varElements(byteCurrentPos)
  Next ' byteCurrentPos
 End If ' bool_Initialized
 
 byteCurrentPos = 0
 byteUbound = 0
 lngElements = 0
 bool_Initialized = False
End Sub ' Delete

End Class ' StringListBig

-Devin

Search

Wowsers! A Tag Cloud!

Links

MiscLinks