Collection Object

Maintained on

When managing multiple pieces of data in VBA, the Collection object provides an alternative to arrays. Collections are more flexible than arrays and make it easy to add and remove data.

This article covers everything from the basics of Collection objects to comparisons with Dictionary, along with practical examples.

What Is a Collection Object?

A Collection object is a built-in VBA object that can store multiple items in ordered sequence. While similar to arrays, it allows for more dynamic and flexible operations.

Key Features of Collections

  • Dynamic sizing: No need to declare the number of elements in advance
  • Mixed data types: Can store strings, numbers, objects, and other types together
  • Order preservation: Data is maintained in the order it was added
  • Key specification: Optionally manage data using keys
  • No reference required: Part of VBA’s standard features—no additional setup needed

Comparison with Arrays

FeatureCollectionArray
Size changes○ Dynamic△ Requires ReDim
Mixed data types○ Allowed× Not allowed
Adding elements○ Easy△ Cumbersome
Removing elements○ Easy△ Cumbersome
IndexStarts at 1Starts at 0*
Performance△ Slightly slower○ Fast

*Arrays can start at different indices depending on Option Base or declaration method

Collection Index

Collection indices always start at 1. Unlike arrays, they never start at 0.

Basic Usage of Collections

Creating an Instance

Create a Collection object using the New keyword.

Creating_a_Collection
Dim myCollection As Collection
Set myCollection = New Collection

' You can also write it in one line
Dim myCollection As New Collection

Add Method - Adding Elements

Use the Add method to add elements to a Collection.

Adding_Elements
Dim fruits As New Collection

' Add elements
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

Debug.Print fruits.Count  ' => 3

Adding with Keys

You can optionally specify a key when adding elements.

Adding_with_Keys
Dim prices As New Collection

' First argument: value, Second argument: key
prices.Add Item:=100, Key:="apple"
prices.Add 150, "banana"
prices.Add 120, "orange"

' Retrieve values using keys
Debug.Print prices("apple")   ' => 100
Debug.Print prices("banana")  ' => 150
Duplicate Keys

Attempting to add an element with a duplicate key will cause an error: “This key is already associated with an element of this collection.” Keys must be unique.

Adding at Specific Positions

Use the Before or After parameter to add elements at specific positions.

Adding_at_Position
Dim items As New Collection

items.Add "First"
items.Add "Third"

' Add after "First"
items.Add "Second", After:=1

' Result: "First", "Second", "Third"

Item Property - Retrieving Elements

Retrieve elements by specifying an index or key.

Retrieving_Elements
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

' Retrieve by index (starts at 1)
Debug.Print fruits.Item(1)  ' => apple
Debug.Print fruits(1)       ' Item can be omitted

' Retrieve by key (when added with a key)
Dim prices As New Collection
prices.Add 100, "apple"

Debug.Print prices("apple")  ' => 100

Remove Method - Removing Elements

Remove elements by specifying an index or key.

Removing_Elements
Dim fruits As New Collection
fruits.Add "apple", "apple"
fruits.Add "banana", "banana"
fruits.Add "orange", "orange"

' Remove by index
fruits.Remove 2

' Remove by key
fruits.Remove "apple"

Debug.Print fruits.Count  ' => 1
Removing Non-existent Elements

Attempting to remove an element that doesn’t exist will cause an error. Always verify existence before removing.

Count Property - Getting the Number of Elements

Getting_Count
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"

Debug.Print fruits.Count  ' => 2

Iterating Through a Collection

Using For Each Loop

The most common way to iterate through a Collection is using For Each.

For_Each_Loop
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

Dim fruit As Variant
For Each fruit In fruits
    Debug.Print fruit
Next fruit

Using For Loop with Index

For_Loop_with_Index
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

Dim i As Long
For i = 1 To fruits.Count
    Debug.Print i & ": " & fruits(i)
Next i

Collection vs Dictionary

Both Collection and Dictionary can store data as key-value pairs, but they have different strengths.

FeatureCollectionDictionary
Key existence check× Not available○ Available
Update by key× Not available○ Available
Get all keys× Not available○ Available
Reference setupNot requiredRequired*
Search speed△ Slower○ Faster

*Dictionary requires “Microsoft Scripting Runtime” reference or CreateObject

When to Use Collection

  • When you need ordered storage without key access
  • When keeping code simple without external references
  • When performance is not critical

When to Use Dictionary

  • When you need key-based lookup
  • When you need to check if a key exists
  • When high-performance search is required

Practical Examples

Removing Duplicates from Data

Removing_Duplicates
Function RemoveDuplicates(sourceArray As Variant) As Collection
    Dim result As New Collection
    Dim item As Variant

    On Error Resume Next
    For Each item In sourceArray
        ' Adding with the same key throws an error, so duplicates are skipped
        result.Add item, CStr(item)
    Next item
    On Error GoTo 0

    Set RemoveDuplicates = result
End Function

Sub TestRemoveDuplicates()
    Dim data As Variant
    data = Array("apple", "banana", "apple", "orange", "banana")

    Dim uniqueItems As Collection
    Set uniqueItems = RemoveDuplicates(data)

    Dim item As Variant
    For Each item In uniqueItems
        Debug.Print item
    Next item
    ' Output: apple, banana, orange
End Sub

Managing Objects

Collections are especially useful for managing objects.

Managing_Objects
Sub ManageEmployees()
    Dim employees As New Collection

    ' Add employee objects (using Dictionary for simplicity)
    Dim emp1 As Object
    Set emp1 = CreateObject("Scripting.Dictionary")
    emp1("name") = "John Smith"
    emp1("department") = "Sales"
    emp1("salary") = 50000

    Dim emp2 As Object
    Set emp2 = CreateObject("Scripting.Dictionary")
    emp2("name") = "Jane Doe"
    emp2("department") = "Engineering"
    emp2("salary") = 65000

    employees.Add emp1, emp1("name")
    employees.Add emp2, emp2("name")

    ' Retrieve by name
    Debug.Print employees("John Smith")("department")  ' => Sales

    ' Iterate through all employees
    Dim emp As Variant
    For Each emp In employees
        Debug.Print emp("name") & " - " & emp("department")
    Next emp
End Sub

Stack Implementation (LIFO)

Stack_Implementation
' Simple stack using Collection
Dim stack As New Collection

Sub Push(value As Variant)
    stack.Add value
End Sub

Function Pop() As Variant
    If stack.Count > 0 Then
        Pop = stack(stack.Count)
        stack.Remove stack.Count
    Else
        Pop = Null
    End If
End Function

Sub TestStack()
    Push "First"
    Push "Second"
    Push "Third"

    Debug.Print Pop()  ' => Third
    Debug.Print Pop()  ' => Second
    Debug.Print Pop()  ' => First
End Sub

Error Handling

Common Errors and Solutions

Key Already Exists Error

Handling_Duplicate_Key
Sub SafeAdd(col As Collection, item As Variant, key As String)
    On Error Resume Next
    col.Add item, key
    If Err.Number = 457 Then
        ' Key already exists - update not possible with Collection
        Debug.Print "Key '" & key & "' already exists"
    End If
    On Error GoTo 0
End Sub

Index Out of Range Error

Handling_Invalid_Index
Function SafeGetItem(col As Collection, index As Long) As Variant
    If index >= 1 And index <= col.Count Then
        SafeGetItem = col(index)
    Else
        SafeGetItem = Null
        Debug.Print "Index " & index & " is out of range"
    End If
End Function

Summary

The Collection object is a powerful data structure in VBA that offers flexibility beyond arrays:

  • Dynamic sizing: No need to specify size in advance
  • Mixed data types: Store different types in one collection
  • Easy operations: Simple add and remove operations
  • Optional keys: Access items by key when needed

Use Collection when you need simple, ordered storage. For advanced key-based operations, consider using Dictionary instead.

#VBA #Collection #Data Structure #Object-Oriented