VBA Course: Arrays (Exercise)

Practical Exercise

To practice using arrays, you will step-by-step create the macro that was used as an example to demonstrate the speed of arrays.

The file: arrays-exercise.xlsm


For this exercise, the database has been reduced to 1000 rows.

bd vba arrays exercise

Exercise objective: the procedure should loop through the database and count the number of YES or NO (according to the user's choice) for each year and customer number, and enter this count into the corresponding cell.

excel table customers fiscal years png vba arrays exercise

Complete the following macro before moving on to the solution:

Sub exercise()
    
    'Last row of the database
    '...

    'Value to search for (YES or NO)
    '...
    
    'Declaration of dynamic array
    Dim dataArray()
    '...
    
    'Storing data in the array
    '...
    
    'Counting YES or NO
    '...
    
End Sub

.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.
.

Here is a solution to complete this exercise (additional information is available below):

Sub exercise()

    Dim lastDataRow As Integer, searchValue As String, number As Integer, counter As Integer, line As Integer, y As Integer, c As Integer, i As Integer

    'Last row of the database
    lastDataRow = Sheets("DB").Cells(Rows.Count, 1).End(xlUp).Row

    'Value to search for (YES or NO)
    If Sheets("Grid").OptionButton_yes Then
        searchValue = "YES"
    Else
        searchValue = "NO"
    End If

    'Declaration of dynamic array
    Dim dataArray()
    ReDim dataArray(lastDataRow - 2, 1)

    'Number of the first record in the array
    number = 0

    'Storing data in the array
    For line = 2 To lastDataRow
        If Sheets("DB").Range("C" & line) = searchValue Then
            dataArray(number, 0) = Year(Sheets("DB").Range("A" & line)) 'Year of the date
            dataArray(number, 1) = Sheets("DB").Range("B" & line) 'Customer number
            number = number + 1
        End If
    Next

    'Counting YES or NO
    For y = 2011 To 2026 'Loop through the years
        For c = 1 To 30 'Loop through the customers

            'Counter for YES or NO
            counter = 0
            For i = 0 To number - 1
                If dataArray(i, 0) = y And dataArray(i, 1) = c Then counter = counter + 1
            Next

            'Display in the cell
            Cells(y - 2009, c + 1) = counter

        Next
    Next

End Sub

Last Row

Calculating the last data row of the DB sheet (explained in the previous exercise):

'Last row of the database
lastDataRow = Sheets("DB").Cells(Rows.Count, 1).End(xlUp).Row

Search Value

If the OptionButton_yes control (on the Grid sheet) is selected, it should search for YES; otherwise, it should search for NO:

'Value to search for (YES or NO)
If Sheets("Grid").OptionButton_yes Then
    searchValue = "YES"
Else
    searchValue = "NO"
End If

Array Declaration

In this case, it would have been possible to calculate the number of YES or NO from the DB sheet in order to resize the dynamic array to the exact number of data it is about to receive.

However, to avoid this additional calculation, the array is simply resized here to the size of the database:

'Declaration of dynamic array
Dim dataArray()
ReDim dataArray(lastDataRow - 2, 1)

Number

The number variable will determine the position of the records in the array (and starts at 0):

'Number of the first record in the array
number = 0

Storing Data in the Array

The For loop iterates through each line of the database and stores the information in the array if column C contains the search value:

'Storing data in the array
For line = 2 To lastDataRow
    If Sheets("DB").Range("C" & line) = searchValue Then
        dataArray(number, 0) = Year(Sheets("DB").Range("A" & line)) 'Year of the date
        dataArray(number, 1) = Sheets("DB").Range("B" & line) 'Customer number
        number = number + 1
    End If
Next

To avoid recalculating the year of each date in the array in the following loops, only the year of the date is stored in the array.

After each entry in the array, the number variable is incremented by 1 for the next entry.

Counting

The For loop here iterates through each data row of the array (from 0 to number - 1 which corresponds to the number of the last entry) and checks for matches for the defined year and defined customer number:

'Counter for YES or NO
counter = 0
For i = 0 To number - 1
    If dataArray(i, 0) = y And dataArray(i, 1) = c Then counter = counter + 1
Next

The result is then inserted into the cell corresponding to the defined year and defined customer number:

'Display in the cell
Cells(y - 2009, c + 1) = counter

Finally, you just need to repeat these operations for each year and each customer number by adding them between two For loops:

'Counting YES or NO
For y = 2011 To 2026 'Loop through the years
    For c = 1 To 30 'Loop through the customers

        'Counter for YES or NO
        counter = 0
        For i = 0 To number - 1
            If dataArray(i, 0) = y And dataArray(i, 1) = c Then counter = counter + 1
        Next

        'Display in the cell
        Cells(y - 2009, c + 1) = counter

    Next
Next

ScreenUpdating

We haven't seen it yet, but you can still add the following line at the beginning of the procedure to speed up the execution of the macro:

Application.ScreenUpdating = False

By adding this line, you instruct Excel not to update the display until the procedure is complete.

In this case, instead of seeing each number being added one by one in the cells, all the numbers will be displayed at once.

File

The completed file: arrays-completed-exercise.xlsm

excel table customers years numbers png vba arrays exercise