Use a VBA dictionary to create a collection of key-value pairs. The VBA dictionary object links keys to items so you can get your items later by simply calling the key by name. The VBA dictionary is a top-level object in the Microsoft Scripting Runtime object library.

Dictionaries in VBA can be a tough concept to grasp. In this tutorial we’ll first give you a formal definition of what a dictionary is, to avoid any confusion with indexed arrays and collection objects.

Next, we’ll give you a quick rundown of the properties and methods of the VBA dictionary object and then we’ll present two very different uses of the VBA dictionary object to show you the versatility of it. The VBA dictionary examples in this section, including how to use dictionary keys, should be really helpful for you.

Finally, we’ll briefly discuss the conditions which favor the use of dictionaries over other types of objects that hold groups of related data. Yes, there’s a time and a place for VBA dictionaries!

Note, we use the terms “value” and “item” interchangeably throughout the tutorial, though item is the proper term.

Now, let’s start by getting the definition of what a dictionary is straight!


VBA Dictionary Definition

In computer science, the formal dictionary definition states that “a dictionary is an abstract data type composed of a collection of key-value pairs such that each possible key appears at most once in the collection. That is, each key in the dictionary is unique.

Similarly, in an indexed array, each index number is unique and to retrieve the nth value of the indexed array, you simply reference the nth index of it. In dictionaries, on the other hand, the key itself is used to reference the associated value of the key. That means you don’t have to know the index of the value to retrieve it; you only need to know the key.

Because of this functionality, dictionaries are also known as associative arrays. Using these terms interchangeably makes sense in many computer languages, but not so much in VBA, since in VBA you must work with dictionaries through the dictionary object. You cannot simply construct an associative array in VBA with the typical array syntax. Take the following invalid pseudo-code, for example:

' Invalid VBA associative array constructor
Dim varArray () As Variant

varArray("Alice") = "555-778-0131"
varArray("Bob") = "555-202-0114"

Some other programming languages let you define associated arrays like this, but this will not work in VBA. One of the reasons why the code above doesn’t work is that arrays must be dimensioned to a known size in VBA, whereas dictionaries auto-resize when keys are added or removed from them.


VBA Dictionary Properties

The VBA dictionary object has the following properties. Recall that Properties grab information about an object or control the behavior of the object.

Property Description
.CompareMode Gets or sets the compare mode of the dictionary keys.The .CompareMode property can be set to either binary, database or text.
.Count Returns the number of elements (key-value pairs) in the dictionary.
.Item Gets or sets the item (value) of a specific key.
.Key Replaces a key with another key.

In addition to the information in the table above, it’s worth pointing out the following features of VBA dictionaries:

  • Dictionaries Auto-resize. You can practically add as many key-value pairs to a dictionary as you want and, unlike VBA arrays, the dictionary will automatically dimension itself.
  • Properties of keys.
    • By default, the VBA dictionary keys are case-sensitive.
    • The most commonly used data types used for dictionary keys are strings and numbers, but a key can be any input except an array. For this reason, you need to specify the .CompareMode property of the dictionary object accordingly, otherwise the dictionary object won’t be able to distinguish properly between the keys.
  • Properties of items. Items or values can be of any type, including objects, collections and arrays, not just strings or numbers. If you want, you can even create a dictionary of dictionaries!

In short, keys are typically strings or numbers (cannot be an array). Items, which are associated with your keys, can be basically anything.


VBA Dictionary Methods

Before we move on to the VBA Dictionary examples, let’s give you a quick rundown of the methods of the dictionary object. Recall that Methods are actions that an object can perform, so that’s how they differ from properties.

Method Description
.Add Adds a key-value pair to the dictionary.
.Exists Checks whether the specified key already exists in the dictionary.
.Items The array of all items (values) in the dictionary.
.Keys The array of all keys in the dictionary.
.Remove Removes the specified key-value pair from the dictionary.
.Removeall Removes all items (key-value pairs) from the dictionary.

The .Exists method of the dictionary object is extremely useful and one of the main reasons why we generally prefer to work with dictionary objects rather than collection objects in VBA. The .Exists method also distinguishes dictionaries from arrays. In array, you would have to create your own function to check if a value is in an array.

It’s now time to show you how to set up your VBA dictionary object! We’ll demonstrate some creative uses for it to help you get started.


Make powerful macros with our free VBA Developer Kit

It’s easy to copy and paste a macro like this, but it’s harder make one on your own. To help you make macros like this, we built a free VBA Developer Kit and wrote the Big Book of Excel VBA Macros full of hundreds of pre-built macros to help you master file I/O, arrays, strings and more - grab your free copy below.

I'll take a free VBA Developer Kit

Basic setup of a VBA Dictionary

For early binding, start by opening the Visual Basic Editor by pressing Alt+F11 and going to Tools > References. Set a reference to the Microsoft Scripting Runtime object library.

VBA Microsoft Scripting Runtime Reference
VBA Microsoft Scripting Runtime Reference

Next, paste the code below into a standard code module:

Sub DictionaryBasicSetup()
    ' (1) set up the VBA dictionary object (Tools > References > Microsoft Scripting Runtime)
    ' (2) insert two random values in the dictionary
    ' (3) print the values to the immediate window be referencing the keys
    Dim dict As Scripting.Dictionary

    Set dict = New Scripting.Dictionary
    
    ' insert some random items
    dict("Alice") = "555-778-0131" 
    dict("Bob") = "555-202-0114"
    
    ' print items to the immediate window
    Debug.Print dict("Alice")
    Debug.Print dict("Bob")

End Sub

When you run this macro, you’ll be able to see how the keys are linked, or associated, with the items (phone numbers, in this case). That’s why we call the pairs key-value pairs, or key-item pairs.

We used early binding, by means of the New operator, to allow us to view the methods and properties of the dictionary object at design time with the “Auto List Members” feature of the Visual Basic Editor.

VBA Dictionary Auto List Members
VBA Dictionary Auto List Members

The next couple examples are going to be more difficult to understand, but I encourage you to try the macros for yourself so you’ll have a better understanding of how dictionaries in VBA work and how you can use them in your own projects.


List of unique numbers with VBA Dictionary

Just to show you how powerful the .Exists method of the dictionary object is, we’ll start by showing you an easy way to create a list of unique randomly generated numbers with it.

Sub CallGenerateUniqueNumbersList()

    Dim varUniqueNumbersList As Variant
    
    varUniqueNumbersList = GenerateUniqueNumbersList(10, 1, 100)
    
    ' print list to immediate window
    If IsArray(varUniqueNumbersList) Then 
    	' *********************************************
    	'Insert your code here
    	' *********************************************
    	Debug.Print Join(varUniqueNumbersList, ";") ' remove in production
    End If

End Sub

Function GenerateUniqueNumbersList(ListLength As Integer, LowerBound As Integer, UpperBound As Integer) As Variant
    'Must add reference to Tools > References > Microsoft Scripting Runtime

    Dim dict As Scripting.Dictionary
    Dim i As Integer
    Dim var As Variant
    
    ' error handling
    If ListLength > UpperBound Then
        MsgBox "The length of the list cannot exceed the upper bound.", vbCritical, "Error!"
        Exit Function
    End If
    
    Set dict = New Scripting.Dictionary
    
    ' fill dictionary keys with unique random numbers
    With dict
        Do While .Count < ListLength
            i = Int((UpperBound - LowerBound + 1) * Rnd + LowerBound)
            If Not .Exists(i) Then .Add i, ""
        Loop
        GenerateUniqueNumbersList = .Keys
    End With

End Function

The GenerateUniqueNumbersList function is programmed to generate integers only. You invoke the function with the CallGenerateUniqueNumbersList procedure and in this example, we’ve specified in the parameters that we want the function to return 10 integers in the range from 1-100.

I know this is an odd example. All we do is create random integers and add them as Keys to a dictionary, then we print the keys we created. We don’t actually associate any items with our keys. All we’re doing is demonstrating how you can use the .Exists method to see if a value exists before adding a new one. This way, we’re guaranteed to have unique values in our list of numbers.


Group data in range using VBA Dictionary

In this example, we’ll assume that you’re working in the sales department of a company and that you’ve just compiled a list of all the sales of a given period. You now want to group the data by seller and then perform several calculations on the sales data for a report. You can do similar tasks with the the VBA AutoFilter method or pivot tables, but we’re here to test out our dictionary skills!

First, paste the example data below starting in cell “A1” of an empty sheet:

Order id Item id Quantity Unit price Line total Seller name Unit cost
10 45 1 $10,00 $10,00 A $5,00
11 234 2 $11,00 $22,00 A $6,00
12 45 3 $12,00 $36,00 C $7,00
13 67 4 $13,00 $52,00 B $8,00
14 91 5 $14,00 $70,00 A $9,00
15 23 1 $15,00 $15,00 B $10,00
16 32 2 $16,00 $32,00 C $11,00
17 45 3 $17,00 $51,00 C $12,00
18 54 4 $18,00 $72,00 B $13,00
19 478 5 $19,00 $95,00 B $14,00
20 54 1 $20,00 $20,00 A $15,00

Next, paste the code below into a standard code module:

Sub DictionaryGroupData(rngInput As Range, keyColIndex As Long, blHeaders As Boolean)
    'Must add reference to Tools > References > Microsoft Scripting Runtime
    Dim i As Long
    Dim rngCell As Range, rng As Range, rngTemp As Range
    Dim dict As Scripting.Dictionary
    Dim strVal As String
    Dim varOrigItems As Variant, varUniqueItems As Variant, varKey As Variant, _
        varItem As Variant
    
    Application.ScreenUpdating = False
    
    Set rng = rngInput.Columns(keyColIndex)
    Set dict = New Scripting.Dictionary
    
    ' set compare mode to text
    dict.CompareMode = TextCompare
    
    ' offset by one row if range has headers
    If blHeaders Then
        With rngInput
            Set rngInput = .Offset(1, 0).Resize(.Rows.Count - 1, .Columns.Count)
        End With
    End If
    
    ' add keys and values to dictionary
    With rngInput
        For Each rngCell In rngInput.Columns(keyColIndex).Cells
            i = i + 1
            strVal = rngCell.Text
            
            ' add new key and item range
            If Not dict.Exists(strVal) Then
                dict.Add strVal, .Rows(i)
                
            ' merge item ranges of existing key
            Else
                Set rngTemp = Union(.Rows(i), dict(strVal))
                dict.Remove strVal ' simply updating the item in a loop will cause a run-time error!
                dict.Add strVal, rngTemp
            End If
        Next rngCell
    End With
    
    For Each varKey In dict.Keys
        ' *********************************************
        'Insert your code here
        ' *********************************************
        Debug.Print varKey & ": " & dict.Item(varKey).Address ' remove in production
    Next varKey
    ' *********************************************
    ' or add code here for specific key actions
    ' dict("A").Select
    ' *********************************************
    Application.ScreenUpdating = True

End Sub

Make sure you have your Immediate Window visible (Ctrl), then invoke the procedure the following way:

Sub CallDataGrouper()
Call DictionaryGroupData(Range("A1:G12"), 6, True)
End Sub

VBA Dictionary Key-Item Pairs
VBA Dictionary Key-Item Pairs

This example is actually really cool. It adds each unique seller name as a “Key” in your dictionary, and the associated item is a Range object. That’s right. You’re not storing the values in the ranges; you’re storing the ranges themselves! That means by simply referencing the Seller’s name, you’re able to change the color of the ranges, select the cells in the range, delete the ranges or anything else you could possibly want to do. In our example, we printed the address of the range using the .Address property of our range objects.

If you wanted, you could select all the ranges from seller A by adding (or uncommenting) the following line in the DictionaryGroupData routine:

dict("A").Select

VBA Dictionary to Control Ranges
VBA Dictionary to Control Ranges

It’s pretty neat how easy it is to get item information by simply calling the key by name.

Customizing the DictionaryGroupData Sub

If you’re interested in customizing our DictionaryGroupData macro for your own project, here’s how each argument works.

The first parameter of the procedure, rngInput, is the input data range you want to process.

The second parameter, keyColIndex, is the index of the column by which you group the data range, in this case the seller name. You want to make absolutely sure that all entries in this column have a one-to-one correspondence with what they’re referring to, in this case the seller. In real-life situations, two sellers might have the same name, which would render the grouping of sales records invalid. However, for the purposes of this example, we simply assume that this condition is met.

The third parameter, blHeaders, is a Boolean type variable which specifies whether the input data range has a header row. The default value is False, but in this example, we’ve set this parameter to True since the first row of the example data is a header row. Being able to specify this is particularly useful in case you want to pass a named range to the procedure, since such ranges may or may not contain headers, depending on how they were originally defined.

In our example, the procedure will use VBA dictionary key-value pairs to group all rows of each seller into combined non-contiguous ranges and then print the addresses of these ranges in the immediate window.

Since the associated items are Ranges instead of basic strings or numbers, you can directly manipulate the ranges however you want. After having grouped the data and identified where related data is in your sheet, you can now manipulate it any way you see fit in your report for management!


VBA Dictionary Application Ideas

Working with dictionaries is particularly powerful when one or more of the following conditions are met:

  • Unique values. At least one of the dimensions (data columns) in your data set should contain unique values, or at least the values should have a one-to-one correspondence to what they’re referring to.
  • The number of required items is unknown. Unlike VBA arrays, dictionaries auto-resize when new keys are added to them, or removed from them. This makes them much easier to work with than arrays when you don’t know in advance how many items you’ll be working with.
  • Intuitive referencing. Most people find it easier to remember names of keys rather than index numbers.

If none of the conditions above are met, it makes very little sense to use dictionaries. In that case you probably want to resort an array or collection object instead.

That’s all for this tutorial. When you’re ready to take your VBA to the next level, subscribe using the form below.