Dictionary Object

Maintained on

The Dictionary object is one of the most efficient ways to manage data in VBA. It stores data as key-value pairs, enabling flexible operations that are difficult to achieve with arrays or Collection objects.

This article covers everything from basic Dictionary usage to practical examples.

What Is a Dictionary Object?

A Dictionary object is a data structure that stores data as key-value pairs. In other programming languages, it’s often called an “associative array,” “hash table,” or “map.”

Key Features

  • Fast key-based lookup: Access values using arbitrary keys instead of index numbers
  • Uniqueness guarantee: Duplicate keys aren’t allowed, preventing data duplication
  • Flexible data types: Various data types can be used for both keys and values
  • Dynamic sizing: No need to declare the size in advance, unlike arrays

Comparison with Collection

VBA also has a Collection object with similar functionality, but Dictionary excels in these areas:

FeatureDictionaryCollection
Key existence check○ Available× Not available
Update value by key○ Available× Not available
Get all keys○ Available× Not available
Fast search○ Fast△ Slow
Reference Setting

To use the Dictionary object, you need a reference to “Microsoft Scripting Runtime.” However, you can also use it without the reference by using CreateObject("Scripting.Dictionary").

Basic Dictionary Usage

Using Reference Setting

In the VBA Editor, go to “Tools” → “References” and check “Microsoft Scripting Runtime.”

Using_Reference
Dim dict As Scripting.Dictionary
Set dict = New Scripting.Dictionary

' Add values
dict.Add "apple", 100
dict.Add "banana", 150
dict.Add "orange", 120

' Retrieve value
Debug.Print dict("apple")  ' => 100

This method works without reference settings, making it more portable across environments.

Using_CreateObject
Dim dict As Object
Set dict = CreateObject("Scripting.Dictionary")

' Add values
dict.Add "apple", 100
dict.Add "banana", 150
dict.Add "orange", 120

' Retrieve value
Debug.Print dict("apple")  ' => 100
Recommended Approach

The CreateObject approach doesn’t require reference settings and works across different environments. Unless you have specific reasons, this method is recommended.

Key Properties and Methods

Add Method - Adding Elements

Adds a new key-value pair to the Dictionary.

Add_Method
dict.Add Key:="apple", Item:=100
dict.Add "banana", 150  ' Argument names can be omitted

' Adding a duplicate key throws an error
' dict.Add "apple", 200  ' Error: This key is already associated
Duplicate Keys

Calling Add with a duplicate key causes an error. Either check if the key exists first, or use the Item property to overwrite.

Item Property - Getting/Setting Values

Gets or sets the value for a specified key.

Item_Property
' Get value
Dim price As Long
price = dict.Item("apple")  ' => 100
price = dict("apple")       ' Item can be omitted

' Set value (overwrite)
dict.Item("apple") = 200
dict("apple") = 200  ' Item can be omitted

' Non-existent key is automatically added
dict("grape") = 180  ' Added automatically
Item Property Behavior

When you assign a value to a non-existent key, it’s automatically added to the Dictionary. This allows you to set values without checking with Exists first.

Exists Method - Checking Key Existence

Checks whether a specified key exists in the Dictionary.

Exists_Method
If dict.Exists("apple") Then
    Debug.Print "Apple exists"
Else
    Debug.Print "Apple does not exist"
End If

' Use in conditional logic
If Not dict.Exists("melon") Then
    dict.Add "melon", 300
End If

Remove Method - Removing Elements

Removes an element with the specified key.

Remove_Method
dict.Remove "banana"

' Removing non-existent key throws an error
If dict.Exists("melon") Then
    dict.Remove "melon"
End If

RemoveAll Method - Removing All Elements

Removes all elements from the Dictionary.

RemoveAll_Method
dict.RemoveAll

Debug.Print dict.Count  ' => 0

Count Property - Getting Element Count

Gets the number of elements stored in the Dictionary.

Count_Property
Debug.Print "Element count: " & dict.Count

' Use in loops
If dict.Count > 0 Then
    Debug.Print "Data exists"
End If

Keys Method - Getting All Keys

Returns all keys stored in the Dictionary as an array.

Keys_Method
Dim allKeys As Variant
allKeys = dict.Keys

Dim i As Long
For i = 0 To UBound(allKeys)
    Debug.Print allKeys(i)
Next i

Items Method - Getting All Values

Returns all values stored in the Dictionary as an array.

Items_Method
Dim allItems As Variant
allItems = dict.Items

Dim i As Long
For i = 0 To UBound(allItems)
    Debug.Print allItems(i)
Next i

Iterating Through a Dictionary

Using For Each Loop

For_Each_Loop
Dim key As Variant
For Each key In dict.Keys
    Debug.Print key & ": " & dict(key)
Next key

Using For Loop with Index

For_Loop
Dim keys As Variant
keys = dict.Keys

Dim i As Long
For i = 0 To dict.Count - 1
    Debug.Print keys(i) & ": " & dict(keys(i))
Next i

Practical Examples

Counting Word Frequency

Word_Frequency
Sub CountWordFrequency()
    Dim dict As Object
    Set dict = CreateObject("Scripting.Dictionary")

    Dim words As Variant
    words = Array("apple", "banana", "apple", "orange", "banana", "apple")

    Dim word As Variant
    For Each word In words
        If dict.Exists(word) Then
            dict(word) = dict(word) + 1
        Else
            dict(word) = 1
        End If
    Next word

    ' Display results
    Dim key As Variant
    For Each key In dict.Keys
        Debug.Print key & ": " & dict(key) & " times"
    Next key
    ' Output:
    ' apple: 3 times
    ' banana: 2 times
    ' orange: 1 times
End Sub

Creating a Data Lookup Table

Lookup_Table
Sub CreateLookupTable()
    Dim productPrices As Object
    Set productPrices = CreateObject("Scripting.Dictionary")

    ' Register product prices
    productPrices("P001") = 1000
    productPrices("P002") = 1500
    productPrices("P003") = 2000
    productPrices("P004") = 800

    ' Look up price by product code
    Dim productCode As String
    productCode = "P002"

    If productPrices.Exists(productCode) Then
        Debug.Print "Price of " & productCode & ": $" & productPrices(productCode)
    Else
        Debug.Print "Product not found"
    End If
End Sub

Grouping Data by Category

Data_Grouping
Sub GroupDataByCategory()
    Dim categoryData As Object
    Set categoryData = CreateObject("Scripting.Dictionary")

    ' Sample data: (Name, Category, Amount)
    Dim data As Variant
    data = Array( _
        Array("Item A", "Category 1", 100), _
        Array("Item B", "Category 2", 200), _
        Array("Item C", "Category 1", 150), _
        Array("Item D", "Category 3", 300), _
        Array("Item E", "Category 2", 250))

    ' Group by category
    Dim row As Variant
    Dim category As String
    For Each row In data
        category = row(1)
        If Not categoryData.Exists(category) Then
            categoryData(category) = 0
        End If
        categoryData(category) = categoryData(category) + row(2)
    Next row

    ' Display totals by category
    Dim key As Variant
    For Each key In categoryData.Keys
        Debug.Print key & " Total: $" & categoryData(key)
    Next key
End Sub

Removing Duplicates from Data

Remove_Duplicates
Function GetUniqueValues(sourceRange As Range) As Variant
    Dim dict As Object
    Set dict = CreateObject("Scripting.Dictionary")

    Dim cell As Range
    For Each cell In sourceRange
        If Not IsEmpty(cell.Value) Then
            dict(cell.Value) = True  ' Using key automatically removes duplicates
        End If
    Next cell

    GetUniqueValues = dict.Keys
End Function

Sub TestUniqueValues()
    Dim uniqueValues As Variant
    uniqueValues = GetUniqueValues(Range("A1:A100"))

    Dim i As Long
    For i = 0 To UBound(uniqueValues)
        Debug.Print uniqueValues(i)
    Next i
End Sub

CompareMode Property

The CompareMode property controls how keys are compared.

ValueConstantDescription
0vbBinaryCompareCase-sensitive (default)
1vbTextCompareCase-insensitive
CompareMode
Sub CompareModeExample()
    Dim dict As Object
    Set dict = CreateObject("Scripting.Dictionary")

    ' Case-sensitive (default)
    dict.CompareMode = vbBinaryCompare
    dict.Add "Apple", 100
    dict.Add "apple", 200  ' Treated as different key
    Debug.Print dict.Count  ' => 2

    ' Reset
    Set dict = CreateObject("Scripting.Dictionary")

    ' Case-insensitive
    dict.CompareMode = vbTextCompare
    dict.Add "Apple", 100
    ' dict.Add "apple", 200  ' This would throw an error (duplicate key)
    Debug.Print dict.Count  ' => 1
End Sub
Setting CompareMode

CompareMode must be set before adding any elements. Changing it after adding elements causes an error.

Summary

The Dictionary object is a powerful tool for efficient data management in VBA:

  • Fast key-based lookup: Retrieve data instantly using keys
  • Uniqueness guarantee: Duplicate keys aren’t allowed
  • Flexible operations: Check existence, update values, get all keys/values
  • Dynamic sizing: No need to declare size in advance

Master the Dictionary object to write more efficient and maintainable VBA code.

#VBA #Dictionary #Data Structure #Efficiency