52
\$\begingroup\$

Recently I decided VB6's Collection wasn't enough for my needs, so I decided to implement something like C#'s List<T>. Here's the class that resulted, I'd like to know if the implementation could be made better /more efficient, especially with Insert and Sort methods; also I'd like another pair of eyes to examine the errors being raised and see if it all makes sense - the idea isn't to throw every error that's possible to get with a List<T>, but I might have missed throwing an error that could help usability.

I've been using this List class in VB6 code for a little less than a week now, and seriously, it's like the best thing since sliced bread - being able to add items inline is awesome, and all those members make Collection look awfully boring and make me want to implement a keyed version, which I'm guessing could wrap a Dictionary instead.

Class definition and private functions

As with all classes I write, I start with declaring a Private Type that defines what the class encapsulates, and then I make a private instance of that type which I call this and in the rest of the code I refer to this, which does not have the same meaning as Me (Me refers to the current instance of the List class, while this refers to the encapsulated stuff - as you'll notice I only use Me when I have to).

I have a debate with myself as to whether the RaiseErrorXXXX procedures should be made public or not - doing so would document the errors thrown at the API level, but wouldn't serve any real purpose.

Attribute VB_Name = "List"
Private Type tList
 Encapsulated As Collection
 ItemTypeName As String
End Type
Private this As tList
Option Explicit
Private Function IsReferenceType() As Boolean
 If Count = 0 Then Exit Function
 IsReferenceType = IsObject(this.Encapsulated(1))
End Function
Private Function IsComparable() As Boolean
 If IsReferenceType Then
 IsComparable = TypeOf First Is IComparable
 End If
End Function
Private Function CompareReferenceTypes(value As Variant, other As Variant) As Integer
 Dim comparable As IComparable
 If IsComparable Then
 Set comparable = value
 CompareReferenceTypes = comparable.CompareTo(other)
 Else
 RaiseErrorMustImplementIComparable "CompareReferenceTypes()"
 End If
End Function
Private Function CompareValueTypes(value As Variant, other As Variant) As Integer
 If value < other Then
 CompareValueTypes = -1
 ElseIf value > other Then
 CompareValueTypes = 1
 End If
End Function
Private Function IsEquatable() As Boolean
 If IsReferenceType Then
 IsEquatable = TypeOf First Is IEquatable
 End If
End Function
Private Function EquateReferenceTypes(value As Variant, other As Variant) As Boolean
 Dim equatable As IEquatable
 If IsEquatable Then
 Set equatable = value
 EquateReferenceTypes = equatable.Equals(other)
 Else
 Debug.Print "WARNING: Reference type doesn't implement IEquatable, using reference equality."
 EquateReferenceTypes = (ObjPtr(value) = ObjPtr(other))
 End If
End Function
Private Function EquateValueTypes(value As Variant, other As Variant) As Boolean
 EquateValueTypes = (value = other)
End Function
Private Function ValidateItemType(value As Variant)
 If this.ItemTypeName = vbNullString Then this.ItemTypeName = TypeName(value)
 ValidateItemType = IsTypeSafe(value)
End Function
Private Sub RaiseErrorUnsafeType(member As String, suppliedType As String)
 Err.Raise 13, StringFormat("{0}.{1}", ToString, member), _
 StringFormat("Type Mismatch. Expected: '{0}', '{1}' was supplied.", this.ItemTypeName, suppliedType)
End Sub
Private Sub RaiseErrorMustImplementIComparable(member As String)
 Err.Raise 5, StringFormat("{0}.{1}", ToString, member), "Invalid operation: method requires a list of numeric, date or string values, or a list of objects implementing the IComparable interface."
End Sub
Private Sub Class_Initialize()
 Set this.Encapsulated = New Collection
End Sub
Private Sub Class_Terminate()
 Set this.Encapsulated = Nothing
End Sub

Public Properties

Public Property Get Item(ByVal Index As Long) As Variant
Attribute Item.VB_UserMemId = 0
'Gets the element at the specified index.
 If IsReferenceType Then
 Set Item = this.Encapsulated(Index)
 Else
 Item = this.Encapsulated(Index)
 End If
End Property
Public Property Let Item(ByVal Index As Long, ByVal value As Variant)
'Sets the element at the specified index.
 If Not IsTypeSafe(value) Then RaiseErrorUnsafeType "Item(Let)", TypeName(value)
 RemoveAt Index
 If Index = Count Then
 Add value
 Else
 Insert Index, value
 End If
End Property
Public Property Set Item(ByVal Index As Long, ByVal value As Variant)
'Sets the element at the specified index.
 If Not IsTypeSafe(value) Then RaiseErrorUnsafeType "Item(Set)", TypeName(value)
 RemoveAt Index
 If Index = Count Then
 Add value
 Else
 Insert Index, value
 End If
End Property
Public Property Get NewEnum() As IUnknown
Attribute NewEnum.VB_UserMemId = -4
Attribute NewEnum.VB_MemberFlags = "40"
'Gets an enumerator that iterates through the List.
 Set NewEnum = this.Encapsulated.[_NewEnum]
End Property
Public Property Get Count() As Long
 Count = this.Encapsulated.Count
End Property

Public Methods/Functions

Those are listed in alphabetical order:

Public Sub Add(value As Variant)
'Adds an object to the end of the List.
 If Not ValidateItemType(value) Then RaiseErrorUnsafeType "Add()", TypeName(value)
 this.Encapsulated.Add value
End Sub
Public Sub AddArray(values() As Variant)
'Adds the specified elements to the end of the List.
 Dim value As Variant, i As Long
 For i = LBound(values) To UBound(values)
 Add values(i)
 Next
End Sub
Public Sub AddRange(ByRef values As List)
'Adds the specified elements to the end of the List.
 Dim value As Variant
 For Each value In values
 Add value
 Next
End Sub
Public Sub AddValues(ParamArray values())
'Adds the specified elements to the end of the List.
 Dim value As Variant, i As Long
 For i = LBound(values) To UBound(values)
 Add values(i)
 Next
End Sub
Public Sub Clear()
'Removes all elements from the List.
 Do Until Count = 0
 this.Encapsulated.Remove 1
 Loop
End Sub
Public Function Contains(value As Variant) As Boolean
'Determines whether an element is in the List.
 Contains = (IndexOf(value) <> -1)
End Function
Public Function First() As Variant
'Returns the first element of the List.
 If Count = 0 Then Exit Function
 If IsReferenceType Then
 Set First = Item(1)
 Else
 First = Item(1)
 End If
End Function
Public Function GetRange(ByVal Index As Long, ByVal valuesCount As Long) As List
'Creates a copy of a range of elements in the source List.
 Dim result As List
 If Index > Count Then Err.Raise 9 'index out of range
 Dim lastIndex As Long
 lastIndex = IIf(Index + valuesCount > Count, Count, Index + valuesCount)
 Set result = New List
 Dim i As Long
 For i = Index To lastIndex
 result.Add Item(i)
 Next
 Set GetRange = result
End Function
Public Function IndexOf(value As Variant) As Long
'Searches for the specified object and returns the 1-based index of the first occurrence within the entire List.
 Dim found As Boolean
 Dim isRef As Boolean
 isRef = IsReferenceType
 Dim i As Long
 If Count = 0 Then IndexOf = -1: Exit Function
 For i = 1 To Count
 If isRef Then
 found = EquateReferenceTypes(value, Item(i))
 Else
 found = EquateValueTypes(value, Item(i))
 End If
 If found Then IndexOf = i: Exit Function
 Next
 IndexOf = -1
End Function
Public Sub Insert(ByVal Index As Long, value As Variant)
'Inserts an element into the List at the specified index.
 Dim tmp As List
 Set tmp = GetRange(Index, Count)
 RemoveRange Index, Count
 Add value
 AddRange tmp
End Sub
Public Sub InsertArray(ByVal Index As Long, values() As Variant)
'Inserts the specified elements into the List at the specified index.
 Dim tmp As List
 Set tmp = GetRange(Index, Count)
 RemoveRange Index, Count
 AddArray values
 AddRange tmp
End Sub
Public Sub InsertRange(ByVal Index As Long, values As List)
'Inserts the specified elements into the List at the specified index.
 Dim tmp As List
 Set tmp = GetRange(Index, Count)
 RemoveRange Index, Count
 AddRange values
 AddRange tmp
End Sub
Public Sub InsertValues(ByVal Index As Long, ParamArray values())
'Inserts the specified elements into the List at the specified index.
 Dim valuesArray() As Variant
 valuesArray = values
 InsertArray Index, valuesArray
End Sub
Public Function IsSortable() As Boolean
'Determines whether the List can be sorted.
 If Count = 0 Then Exit Function
 Dim firstItem As Variant
 If IsReferenceType Then
 Set firstItem = First
 Else
 firstItem = First
 End If
 IsSortable = IsNumeric(firstItem) _
 Or IsDate(firstItem) _
 Or this.ItemTypeName = "String" _
 Or IsComparable
End Function
Public Function IsTypeSafe(value As Variant) As Boolean
'Determines whether a value can be safely added to the List.
'Returns true if the type of specified value matches the type of items already in the list,
'or it the type of specified value is a numeric type smaller than the type of items already in the list.
'This means a List<Long> can contain Integer values, but a List<Integer> cannot contain Long values.
 Dim result As Boolean
 'most common cases: this.ItemTypeName isn't yet defined, or matches TypeName(value):
 result = this.ItemTypeName = vbNullString Or this.ItemTypeName = TypeName(value)
 If result Then IsTypeSafe = result: Exit Function
 'all other cases demand more processing:
 IsTypeSafe = result _
 Or this.ItemTypeName = "Integer" And StringMatchesAny(TypeName(value), "Byte") _
 Or this.ItemTypeName = "Long" And StringMatchesAny(TypeName(value), "Integer", "Byte") _
 Or this.ItemTypeName = "Single" And StringMatchesAny(TypeName(value), "Long", "Integer", "Byte") _
 Or this.ItemTypeName = "Double" And StringMatchesAny(TypeName(value), "Long", "Integer", "Byte", "Single") _
 Or this.ItemTypeName = "Currency" And StringMatchesAny(TypeName(value), "Long", "Integer", "Byte", "Single", "Double")
End Function
Public Function Last() As Variant
'Returns the last element of the List.
 If Count = 0 Then Exit Function
 If IsReferenceType Then
 Set Last = Item(Count)
 Else
 Last = Item(Count)
 End If
End Function
Public Function LastIndexOf(value As Variant) As Long
'Searches for the specified object and returns the 1-based index of the last occurrence within the entire List.
 Dim found As Boolean
 Dim isRef As Boolean
 isRef = IsReferenceType
 LastIndexOf = -1
 If Count = 0 Then Exit Function
 Dim i As Long
 For i = 1 To Count
 If isRef Then
 found = EquateReferenceTypes(value, Item(i))
 Else
 found = EquateValueTypes(value, Item(i))
 End If
 If found Then LastIndexOf = i
 Next
End Function
Public Function Max() As Variant
'Returns the maximum value in the List.
 Dim isRef As Boolean
 isRef = IsReferenceType
 Dim largest As Variant
 Dim isLarger As Boolean
 Dim i As Long
 For i = 1 To Count
 If isRef Then
 If IsEmpty(largest) Then Set largest = Item(i)
 isLarger = CompareReferenceTypes(Item(i), largest) > 0
 If isLarger Or IsEmpty(Max) Then
 Set largest = Item(i)
 Set Max = largest
 End If
 Else
 If IsEmpty(largest) Then largest = Item(i)
 isLarger = CompareValueTypes(Item(i), largest) > 0
 If isLarger Or IsEmpty(Max) Then
 largest = Item(i)
 Max = largest
 End If
 End If
 Next
End Function
Public Function Min() As Variant
'Returns the minimum value in the List.
 Dim isRef As Boolean
 isRef = IsReferenceType
 Dim smallest As Variant
 Dim isSmaller As Boolean
 Dim i As Long
 For i = 1 To Count
 If isRef Then
 If IsEmpty(smallest) Then Set smallest = Item(i)
 isSmaller = CompareReferenceTypes(Item(i), smallest) < 0
 If isSmaller Or IsEmpty(Min) Then
 Set smallest = Item(i)
 Set Min = smallest
 End If
 Else
 If IsEmpty(smallest) Then smallest = Item(i)
 isSmaller = CompareValueTypes(Item(i), smallest) < 0
 If isSmaller Or IsEmpty(Min) Then
 smallest = Item(i)
 Min = smallest
 End If
 End If
 Next
End Function
Public Sub Reverse()
'Reverses the order of the elements in the entire List.
 Dim tmp As New List
 Do Until Count = 0
 tmp.Add Item(Count)
 RemoveAt Count
 Loop
 AddRange tmp
End Sub
Public Sub Remove(ParamArray values())
'Removes the first occurrence of specified object(s) from the List.
 Dim i As Long
 Dim Index As Long
 For i = LBound(values) To UBound(values)
 Index = IndexOf(values(i))
 If Index <> -1 Then RemoveAt Index
 Next
End Sub
Public Sub RemoveAt(ByVal Index As Long)
'Removes the element at the specified index of the List.
 this.Encapsulated.Remove Index
End Sub
Public Sub RemoveRange(ByVal Index As Long, ByVal valuesCount As Long)
'Removes a range of elements from the List.
 Dim i As Long
 For i = Index To Index + valuesCount - 1
 RemoveAt Index
 Next
End Sub
Public Sub Sort()
'Sorts the elements in the entire List.
 Dim tmp As List
 Dim minValue As Variant
 If Not IsSortable Then RaiseErrorMustImplementIComparable "Sort()"
 Dim isRef As Boolean
 isRef = IsReferenceType
 Set tmp = New List
 Do Until Count = 0
 If isRef Then
 Set minValue = Min
 Else
 minValue = Min
 End If
 tmp.Add minValue
 Remove minValue
 Loop
 AddRange tmp
End Sub
Public Sub SortDescending()
'Sorts the elements in the entire List, in descending order.
 Dim tmp As List
 Dim maxValue As Variant
 If Not IsSortable Then RaiseErrorMustImplementIComparable "SortDescending()"
 Dim isRef As Boolean
 isRef = IsReferenceType
 Set tmp = New List
 Do Until Count = 0
 If isRef Then
 Set maxValue = Max
 Else
 maxValue = Max
 End If
 tmp.Add maxValue
 Remove maxValue
 Loop
 AddRange tmp
End Sub
Public Function ToArray() As Variant()
'Copies the elements of the List to a new array.
 Dim result() As Variant
 ReDim result(1 To Count)
 Dim i As Long
 If Count = 0 Then Exit Function
 If IsReferenceType Then
 For i = 1 To Count
 Set result(i) = Item(i)
 Next
 Else
 For i = 1 To Count
 result(i) = Item(i)
 Next
 End If
 ToArray = result
End Function
Public Function ToString() As String
'Returns a string that represents the current List object.
 ToString = StringFormat("{0}<{1}>", TypeName(Me), Coalesce(this.ItemTypeName, "Variant"))
End Function

Interfaces

This List uses two interfaces adapted from C#, namely IComparable and IEquatable, for the same reasons List<T> needs them - I believe they would work just as well if I changed the instancing from MultiUse to PublicNotCreatable, but that's one foggy area of my VB6 knowledge, so I left it as is:

IComparable:

Option Explicit
Public Function CompareTo(other As Variant) As Integer
End Function

IEquatable:

Option Explicit
Public Function Equals(other As Variant) As Boolean
End Function

A couple helper functions are also used here and there in the class' code - I'm not asking for a review of those, but if you are interested to see more, StringFormat is a custom C#-style VB6/VBA implementation of string.Format() covered here, StringMatchesAny is a custom string helper function covered here, and Coalesce is a simple null-replacement function that considers an empty string as a null value.

asked Oct 13, 2013 at 1:22
\$\endgroup\$
6
  • \$\begingroup\$ I think Add() should take a ParamArray and call AddArray(), so AddValues() could be removed as redundant, just like Remove() does. ...And I'm probably missing a RemoveArray() method. Or is that too many "overload" members? \$\endgroup\$ Commented Oct 18, 2013 at 18:02
  • \$\begingroup\$ One thing : Attribute NewEnum.VB_MemberFlags = "40" is not supported in VBA. It's meant to hide the member from Object Browser and Intelli-sense but has no effect. \$\endgroup\$ Commented Oct 24, 2014 at 13:09
  • \$\begingroup\$ @vba4all indeed. However this code was originally written in VB6 ;) \$\endgroup\$ Commented Oct 24, 2014 at 13:26
  • 1
    \$\begingroup\$ No problem. Any idea if there is a way to hide a member in VBA? (not through COM though - a regular VBA class member ) \$\endgroup\$ Commented Oct 24, 2014 at 13:28
  • 1
    \$\begingroup\$ @MarkHurd it is. But user code can't be hidden, seems they "dumbed down" the VBE to not recognize the member attribute that would hide it. \$\endgroup\$ Commented Jun 5, 2016 at 13:11

3 Answers 3

31
+50
\$\begingroup\$

OK, went through the code and gave this a bit of thought over the past couple of days. As far as the implementation goes, I don't see a whole lot that I would change (that you didn't identify in the answer above) other than a couple nit-picky things. First, is the use of the this variable identifier. I couldn't find anything that justifies the naming and data structure other than imitating a .NET keyword. The Me keyword (as ridiculous as it sounds after writing C# for a while) is obvious to a VB6 programmer - this is not. I would personally stick with individual member variables instead of the Type, but if using the Type I would name it something like memberData. The fact that you were compelled to explain in the post what this refers to in the class is a red flag because it isn't immediately obvious.

The second nit-pick is also related to using .NET metaphors that do not directly map to a VB6 context, but this one comes from the opposite direction (and falls into the "errors being raised" category). A .NET programmer will expect assignments that are not type-safe to fail at compile time, not runtime. For example, this snippet in VB6 compiles and runs without complaint:

Dim first as Variant
Dim second as Variant
first = "String"
second = 1234
first = second
'First is now an integer.
Debug.Print(TypeName(first))

The analogous code in C# doesn't:

var first = "String";
var second = 1234;
//This fails due to implicit conversion:
first = second;

So if the intention is to enforce type safety, the better meta solutions would be to not use Variant types if they can be avoided or to use an IDE plug-in to make sure your assignments are type safe. If the intention is to simply replicate the functionality of the .NET List object, this is an entirely different matter (and one that is both useful and well executed, BTW).

Nit-picking aside, let's get down to the "better /more efficient" side of things. Given that the Collection object in VB6 isn't much more than a glorified array (4 methods - seriously?), I would just skip it entirely and just wrap an array directly. The vast majority of the class just uses the Collection for storage space, and the fact that the intention is to ensure strong typing makes the memory management a lot easier. Note that I am not recommending an array of Variants, and am at risk of getting into StackOverflow territory.

VB6 is based on Window COM, and uses a SAFEARRAY structure to store all of its arrays internally. This (vastly simplified) defines the size of each array element, tracks the number of elements in each dimension, stores a couple COM flags, and holds a pointer to the array data. Since VB6 is COM based, it also has a couple of undocumented functions like for pointer resolution and manipulation and can directly access the Windows API. This gives you the ability to do inserts and deletes into the middle of arrays with memory copy operations instead of iterating over the array or the a Collection.

You can get the underlying data structure like this:

Private Const VT_BY_REF = &H4000&
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (pDst As Any, pSrc As Any, ByVal ByteLen As Long)
'STRUCTS FOR THE SAFEARRAY:
Private Type SafeBound
 cElements As Long
 lLbound As Long
End Type
Private Type SafeArray
 cDim As Integer
 fFeature As Integer
 cbElements As Long
 cLocks As Long
 pvData As Long
 rgsabound As SafeBound
End Type
Private Function GetArrayInfo(vArray As Variant, uInfo As SafeArray) As Boolean
 'NOTE, the array is passed as a variant so we can get it's absolute memory address. This function
 'loads a copy of the SafeArray structure into the UDT.
 Dim lPointer As Long, iVType As Integer
 If Not IsArray(vArray) Then Exit Function 
 With uInfo
 CopyMemory iVType, vArray, 2 'First 2 bytes are the subtype.
 CopyMemory lPointer, ByVal VarPtr(vArray) + 8, 4 'Get the pointer.
 If (iVType And VT_BY_REF) <> 0 Then 'Test for subtype "pointer"
 CopyMemory lPointer, ByVal lPointer, 4 'Get the real address.
 End If
 CopyMemory uInfo.cDim, ByVal lPointer, 16 'Write the safearray to the passed UDT.
 If uInfo.cDim = 1 Then 'Can't do multi-dimensional
 CopyMemory .rgsabound, ByVal lPointer + 16, LenB(.rgsabound)
 GetArrayInfo = True
 End If
 End With
End Function

The beauty of this approach is that because you now have the underlying data structure of the array in a variable, you can just change the pvData pointer to any memory that has been allocated, and set cbElements to the SizeOf() the data type of the list. An Add() function is then just shifting memory one element higher in memory from your insert offset and dropping in the new item, and Remove() is the opposite. What makes this really slick is that you can just point an Variant back at the SafeArray, and VB6 won't even blink because it is exactly what it expects to see.

About now, you're probably wondering when I'm going to get to typing. Gimme a second, because I want to go over Variants first. Again, keep in mind that we are dealing with a COM object and not strictly a VB object. Microsoft put Variants into COM specifically to allow loosely typed languages a way to marshal data via the API to and from strongly typed languages. The way this works is by passing a structure that includes all of the information that the receiving API needs to determine what the underlying data represents. In that VB6 only implements a very small sub-set of the available data types that a Variant can represent (see the MSDN link a couple sentences back), you could conceivably enforce data typing that VB6 doesn't even natively know about.

All you have to do is to examine the Variant as a memory structure instead of passing it through the built in TypeName() function. This is basically what it is doing anyway (and although I can't verify this, I believe the casting functions use the Variant's union to determine whether a Variant can be cast to a strong type). By directly examining these you can bypass the VB runtime and also avoid all of the string handling involved with using TypeName(). This article is a good place to start, although most of the links seem to have died.

Finally, and not for the faint of heart - if you want to have your List return its type without using the ToString function, you can always hook the VB runtime dll itself and intercept function calls to native VB functions. I wouldn't do this in production code personally, but you can get a good start on that here if you want to really start mucking around in the internals. Scroll down and read about trampoline functions. I've never hooked the VB runtime itself, but it shouldn't be different than any other dll as long as you are really careful what functions you use while you're shuffling its memory around.

Disclaimer

If you try this, you will crash your IDE at least once while you are debugging it. Make a habit of never starting a debugging session when you are manually handling memory without saving your source code first.

answered Feb 19, 2014 at 7:00
\$\endgroup\$
0
23
\$\begingroup\$
Public Function ToString() As String
'Returns a string that represents the current List object.
 ToString = StringFormat("{0}<{1}>", TypeName(Me), _
 Coalesce(this.ItemTypeName, "Variant"))
End Function

This means the string representation of this List is "List<Variant>" when this.ItemTypeName is empty or vbNullString.

This function should be somewhere at the very top:

Private Function ValidateItemType(value As Variant)
 If this.ItemTypeName = vbNullString Then this.ItemTypeName = TypeName(value)
 ValidateItemType = IsTypeSafe(value)
End Function

This is where the string representation of the List stops being "List<Variant>" and becomes List<T>


Given this information, there's a flaw in the IsReferenceType function, which might return the wrong result if the list originally contained objects and then was emptied so that Count = 0:

Private Function IsReferenceType() As Boolean
 If Count = 0 Then Exit Function
 IsReferenceType = IsObject(this.Encapsulated(1))
End Function

The correct code should be:

Private Function IsReferenceType() As Boolean
 If this.ItemTypeName = vbNullString Then Exit Function
 IsReferenceType = IsObject(this.Encapsulated(1))
End Function

In these snippets:

Private Function IsComparable() As Boolean
 If IsReferenceType Then
 IsComparable = TypeOf First Is IComparable
 End If
End Function
Private Function IsEquatable() As Boolean
 If IsReferenceType Then
 IsEquatable = TypeOf First Is IEquatable
 End If
End Function

It is assumed that only reference types can implement IComparable and IEquatable, and that is correct in VB6. Therefore, the presence of CompareValueTypes and EquateValueTypes functions is somewhat awkward, but their usage makes a quite enjoyable reading:

 If isRef Then
 '...
 isSmaller = CompareReferenceTypes(Item(i), smallest) < 0
 '...
 Else
 '...
 isSmaller = CompareValueTypes(Item(i), smallest) < 0
 '...
 End If

The Attribute Item.VB_UserMemId = 0 setting in the getter for the Item property makes that getter the type's default property, making Item(i) also be accessible with Me(i). Cool stuff. Even better:

Public Property Get NewEnum() As IUnknown
Attribute NewEnum.VB_UserMemId = -4
Attribute NewEnum.VB_MemberFlags = "40"
'Gets an enumerator that iterates through the List.
 Set NewEnum = this.Encapsulated.[_NewEnum]
End Property

Attribute NewEnum.VB_UserMemId = -4 instructs VB to use this method in For Each loop constructs; this enables AddRange(values As List) to do what it does:

For Each value In values
 Add value
Next

Given AddArray(values() As Variant), I think AddValues(ParamArray values()) could easily replace Add(value As Variant) - if there's only 1 value to add, both methods can be used and that makes it an ambiguous API. Add, AddRange and AddArray should be rewritten as follows:

Public Sub Add(ParamArray values())
'Adds the specified element(s) to the end of the List.
 Dim valuesArray() As Variant
 valuesArray = values
 AddArray valuesArray
End Sub
Public Sub AddRange(values As List)
'Adds the specified elements to the end of the List.
 AddArray values.ToArray
End Sub
Public Sub AddArray(values() As Variant)
'Adds the specified elements to the end of the List.
 Dim value As Variant, i As Long
 For i = LBound(values) To UBound(values)
 If ValidateItemType(value) Then 
 this.Encapsulated.Add values(i)
 Else
 RaiseErrorUnsafeType "AddArray()", TypeName(value)
 End If
 Next
End Sub

If Count = 0 Then Exit Function, wherever it's used, is an opportunity for some RaiseErrorListContainsNoElement, instead of returning an empty Variant or a meaningless False value.


Insert(ByVal Index As Long, value As Variant) and InsertValues(ByVal Index As Long, ParamArray values()) have exactly the same issue as Add and AddValues have; InsertValues should disappear and be replaced with this:

Public Sub Insert(ByVal Index As Long, ParamArray values())
'Inserts the specified element(s) into the List at the specified index.
 Dim valuesArray() As Variant
 valuesArray = values
 InsertArray Index, valuesArray
End Sub

The conditions for IsSortable are somewhat redundant and the firstItem variable only hides intent - accessing the first item isn't expensive enough to take this readability hit (besides this isn't called in a loop), so IsSortable() could be rewritten like this, and again If Count = 0 Then Exit Function is an opportunity for some RaiseErrorListContainsNoElement:

Public Function IsSortable() As Boolean
'Determines whether the List can be sorted.
 If Count = 0 Then RaiseErrorListContainsNoElement "IsSortable()"
 If IsReferenceType Then
 IsSortable = IsComparable
 Else
 IsSortable = IsNumeric(First) _
 Or IsDate(First) _
 Or this.ItemTypeName = "String"
 End If
End Function

IsTypeSafe is interesting. It works, but it's a little too stiff and a bit more effort could be put into accepting Long values within Integer range in a List<Integer>, and so on.


Remove(ParamArray values()) is already consistent with the changes made to Add and Insert, however RemoveRange breaks the naming convention established with AddRange and InsertRange which both take a List as a parameter. Since RemoveRange should keep its .net List<T> meaning, AddRange and InsertRange should be renamed AddList and InsertList, which would be consistent with AddArray and InsertArray.


That's all I can see.

svick
24.5k4 gold badges53 silver badges89 bronze badges
answered Oct 19, 2013 at 5:04
\$\endgroup\$
1
  • 2
    \$\begingroup\$ If I could just change on thing I would modify the IndexOf() method a bit. See my answer for a clue how you can change the IndexOf() and Contains() you could eliminate a few loops which would speed it up a bit \$\endgroup\$ Commented Jan 15, 2014 at 8:29
9
\$\begingroup\$
  • Your implementation of Sort would be optimised by implementing IndexOfMin so that Min = Item(IndexOfMin) (with a caveat for an empty List), but you can then use the O(1) RemoveAt instead of the O(n) Remove at the end of the Do Until loop. Similarly for IndexOfMax, Max and SortDescending, of course. I'd consider making IndexOfMin and IndexOfMax Public to allow other code to use the same optimisation.

  • IMHO, especially from a VB6 POV and contrary to Mat's Mug, sorting an empty List should succeed and return the empty List, not throw an error. I.e. IsSortable should start:

    IsSortable = True
    If Count = 0 Then Exit Function
    

    Your existing Sort and SortDescending implementations don't need to change for this.

  • (EDIT: Added 6 months later :-) ) Your implementation of LastIndexOf should actually be the same as IndexOf, but with For i = Count To 1 Step -1.

Minor quibbles

  • This is more readable (from a VB6 POV, anyway), and, of course, minusculely faster:

    Public Sub RemoveRange(ByVal Index As Long, ByVal valuesCount As Long)
    'Removes a range of elements from the List.
     Dim i As Long
     For i = 1 To valuesCount
     RemoveAt Index
     Next
    End Sub
    
  • value is unused in AddValues.

  • Clear should use RemoveAt 1. ((削除) I've forgotten my VB6 optimisations: (削除ここまで) I know RemoveAt 1 is the standard idiom, but is RemoveAt Count faster? NO: I've checked it and RemoveAt 1 is 9 orders of magnitude faster!)

answered Jun 5, 2016 at 13:03
\$\endgroup\$

Your Answer

Draft saved
Draft discarded

Sign up or log in

Sign up using Google
Sign up using Email and Password

Post as a guest

Required, but never shown

Post as a guest

Required, but never shown

By clicking "Post Your Answer", you agree to our terms of service and acknowledge you have read our privacy policy.

Start asking to get answers

Find the answer to your question by asking.

Ask question

Explore related questions

See similar questions with these tags.