17  Advanced Topics

17.1 Arguments ByVal and ByRef

In VBA, when passing arguments to functions or Sub-Procedures, you can specify whether the argument is passed ByVal (By Value) or ByRef (By Reference).

  • ByVal (By Value): A copy of the argument’s value is passed to the function or Sub-Procedure. Changes made to the parameter within the function or Sub-Procedure do not affect the original variable that was passed.
  • ByRef (By Reference): The function or Sub-Procedure receives a reference to the original variable. Changes made to the parameter within the function or Sub-Procedure directly affect the original variable.
Default Behavior in VBA

The default behavior in VBA is to pass arguments ByRef, which means that the procedure receives a reference to the original variable. Therefore, changes made to the parameter within the procedure directly affect the original variable (because they are both accessing the same memory location).

17.1.1 Passing Variables

In Listing 17.1, we have a Sub-Procedure ModifyDefault that receives two integer arguments var1 and var2. The default behavior in VBA is to pass arguments ByRef, which means that the procedure receives a reference to the original variable. Hence, after calling the Sub-Procedure ModifyDefault, the original variables originalValue1 and originalValue2 are modified: originalValue1 is now 6, and originalValue2 is also 6.

Listing 17.1: Example of passing arguments to a Sub-Procedure in VBA. The default behavior is to pass arguments ByRef, that is, the procedure receives a reference to the original variable. The original variables originalValue1 and originalValue2 are modified after calling the Sub-Procedure ModifyDefault.
Sub ModifyDefault(var1 As Integer, _
                  var2 As Integer)
    
    var1 = var1 + 1
    var2 = var2 + 1

End Sub

Sub ExampleIntegerDefault()

    Dim originalValue1 As Integer
    Dim originalValue2 As Integer
    
    originalValue1 = 5
    originalValue2 = 5
    
    ModifyDefault originalValue1, originalValue2
    
    'originalValue1 is now 6; it was not changed by the procedure.
    Debug.Print "Original Value (Default is ByRef): " & originalValue1
    
    'originalValue2 is now 6; it was modified inside the procedure.
    Debug.Print "Original Value (Default is ByRef): " & originalValue2
    
End Sub

In Listing 17.2, we have a Sub-Procedure ModifyByValByRef that receives two integer arguments byValVar and byRefVar. The first argument is passed ByVal, and the second argument is passed ByRef. While the first argument byValVar is passed ByVal and remains unchanged after calling the Sub-Procedure ModifyByValByRef, the second argument byRefVar is passed ByRef and is modified inside the procedure.

Listing 17.2: Example of passing arguments to a Sub-Procedure in VBA. The first argument is passed ByVal, and the second argument is passed ByRef. After calling the Sub-Procedure ModifyByValByRef, the original variable originalValue1 remains 5, while originalValue2 is modified to 6.
Sub ModifyByValByRef(ByVal byValVar As Integer, _
                     ByRef byRefVar As Integer)
    
    byValVar = byValVar + 1
    byRefVar = byRefVar + 1

End Sub

Sub ExampleIntegerByValByRef()

    Dim originalValue1 As Integer
    Dim originalValue2 As Integer
    
    originalValue1 = 5
    originalValue2 = 5
    
    ModifyByValByRef originalValue1, originalValue2
    
    'originalValue1 remains 5; it was not changed by the procedure.
    Debug.Print "Original Value (ByVal): " & originalValue1
    
    'originalValue2 is now 6; it was modified inside the procedure.
    Debug.Print "Original Value (ByRef): " & originalValue2
    
End Sub

In Listing 17.3, we have a Sub-Procedure ModifyStringByValByRef that receives two string arguments byValVar and byRefVar. Again, the first argument is passed ByVal, and the second argument is passed ByRef. Notice that, after calling the Sub-Procedure ModifyStringByValByRef, the original variable originalValue1 remains unchanged, while originalValue2 is modified (it is now “String1_modified”).

Listing 17.3: Example of passing arguments to a Sub-Procedure in VBA. The first argument is passed ByVal, and the second argument is passed ByRef. After calling the Sub-Procedure ModifyStringByValByRef, the original variable originalValue1 remains unchanged, while originalValue2 is modified (it is now “String1_modified”).
Sub ModifyStringByValByRef(ByVal byValVar As String, _
                        ByRef byRefVar As String)
    
    byValVar = byValVar & "_modified"
    byRefVar = byRefVar & "_modified"

End Sub

Sub ExampleStringByValByRef()

    Dim originalValue1 As String
    Dim originalValue2 As String
    
    originalValue1 = "String1"
    originalValue2 = "String1"
    
    ModifyStringByValByRef originalValue1, originalValue2
    
    'originalValue1 remains String1 (not changed by the procedure)
    Debug.Print "Original Value (ByVal): " & originalValue1
    
    'originalValue2 is now String1_modified
    Debug.Print "Original Value (ByRef): " & originalValue2
    
End Sub

17.1.2 Passing Arrays

Arrays passed as arguments to functions or Sub-Procedures are always passed ByRef. This means that changes made to the array inside the function or Sub-Procedure directly affect the original array.

Therefore, trying to pass an array ByVal will raise a compile error, as shown in Listing 17.4.

Listing 17.4: Example of a wrong declaration of array parameters in VBA. This code will raise a compile error since VBA does not allow passing arrays ByVal.
Sub ModifyArrayByValByRef(ByVal byValArray() As Integer, _
                          ByRef byRefArray() As Integer) `Fail!

However, if you want to pass an array ByVal, you can pass it as a Variant data type. In Listing 17.5, we have a Sub-Procedure ModifyArrayByValByRef that receives two array arguments: byValArray and byRefArray (both as Variant data type). Inside the Sub-Procedure, we redimension the arrays to hold 5 elements and assign the value 6 to the first element. After calling the Sub-Procedure ModifyArrayByValByRef, the original array originalArray1 remains with size 2 (it was not changed by the procedure), while originalArray2 is redimensioned to hold 5 elements.

Listing 17.5: Example of passing arrays to a Sub-Procedure in VBA. The arrays are passed as Variant data type. After calling the Sub-Procedure ModifyArrayByValByRef, the original array originalArray1 (passed ByVal) remains with size 2, while originalArray2 (passed ByRef) is redimensioned to hold 5 elements.
Sub ModifyArrayByValByRef(ByVal byValArray As Variant, _
                          ByRef byRefArray As Variant)
    
    ReDim Preserve byValArray(1 To 5)
    byValArray(1) = 6
    ReDim Preserve byRefArray(1 To 5)
    byRefArray(1) = 6
    
End Sub

Sub ExampleArrayByValByRef()

    ReDim originalArray1(1 To 2) As String
    originalArray1(1) = 5
    ReDim originalArray2(1 To 2) As String
    originalArray2(1) = 5
    
    ModifyArrayByValByRef originalArray1, originalArray2
    
    'originalArray1 remains with size 2; it was not changed by the procedure.
    Debug.Print "Original Value (ByVal): " & UBound(originalArray1)
    
    'originalArray2 redimensioned to hold 5 elements
    Debug.Print "Original Value (ByRef): " & UBound(originalArray2)
    
End Sub

17.2 Macro Recording

VBA provides a feature called Macro Recording that allows you to record your actions in Excel and generate VBA code based on those actions. This feature is useful for automating repetitive tasks or generating VBA code snippets that you can further customize.

To record a macro in Excel:

  1. Go to the Developer tab (if you don’t see the Developer tab, you can enable it in Excel settings).
  2. Click on Record Macro.
  3. Enter a name for your macro, choose where to store it (in the current workbook or in your Personal Macro Workbook), and assign a shortcut key if needed.
  4. Click OK to start recording.
  5. Perform the actions you want to record (e.g., formatting cells, copying data, etc.).
  6. Click on Stop Recording when you finish (you can find this option in the Developer tab).
  7. You can now run your recorded macro by pressing the shortcut key you assigned or by running it from the Developer tab.

When you record a macro, Excel generates VBA code that corresponds to the actions you performed. You can view and edit this code by going to the Developer tab, clicking on Visual Basic, and opening the VBA editor.

Normally, the recorded code is not optimized and may contain unnecessary lines or hardcoded values. You can refine the code by removing unnecessary lines, adding comments, and making it more flexible and reusable (e.g., by using variables and loops).

17.2.1 Example: Recording and Refining a Macro

In Listing 17.6, we have an example of a recorded macro that formats a table (see Table 17.1) in Excel.

Table 17.1: Copy the table to Excel and name the sheet “data” (download the raw data here).
A B C D E
1 Name Age City Occupation Gender
2 John 25 New York Engineer Male
3 Sarah 30 Los Angeles Teacher Female
4 Michael 22 Chicago Student Male
5 Emily 22 San Francisco Doctor Female

To create this macro we:

  1. In the Developer tab, we clicked on Record Macro.
  2. Entered the name “FormatTable” and stored it in the current workbook.
  3. Assigned no shortcut key.
  4. Pressed OK to start recording.
  5. Clicked on cell “A1” from sheet “data”.
  6. Pressed Ctrl+Shift+Right to select all columns until the right-most column.
  7. Pressed Ctrl+Shift+Down to select all rows until the last row.
  8. Clicked on Insert > Table.
  9. Formated the table with style “White, Table Style Medium 1” (in Table Desing > Table Styles).
  10. Stopped recording (click on Stop Recording in the Developer tab).
Listing 17.6: Example of a recorded macro in VBA. The recorded macro formats a table in Excel by selecting a range, creating a table, and applying a specific style. Notice that the recorded code contains hardcoded values (e.g., $A$1:$E$10, "Table1", "A1"), which can be replaced with variables for more flexibility.
Option Explicit

Sub FormatTable()

    Range("A1").Select
    Range(Selection, Selection.End(xlToRight)).Select
    Range(Selection, Selection.End(xlDown)).Select
    Application.CutCopyMode = False
    ActiveSheet.ListObjects.Add(xlSrcRange, Range("$A$1:$E$10"), , xlYes).name = "Table1"
    Range("Table1[#All]").Select
    ActiveSheet.ListObjects("Table1").TableStyle = "TableStyleMedium1"

End Sub

Access your VBA editor by clicking on Visual Basic in the Developer tab and open the module where the recorded macro is stored. In the recorded macro FormatTable, the code selects a specific range ($A$1:$E$10), creates a table, and applies a specific style (TableStyleMedium1). In Listing 17.7, we have a refined version of the recorded macro that uses variables for the range and table name, making the code more flexible and reusable.

To refine the recorded macro, we:

  1. Created a Sub-Procedure FormatRangeAsTable that takes two parameters:
    • targetRange (the range to format) and
    • tableName (the name of the table).
  2. Removed the hardcoded values and replaced them with the parameters targetRange and tableName.
  3. Removed the lines that were selecting cells:
    • Range("A1").Select,
    • Range(Selection, Selection.End(xlToRight)).Select, and
    • Range(Selection, Selection.End(xlDown)).Select.
  • Removed line Application.CutCopyMode = False
  • Replaced ActiveSheet.ListObjects.Add(xlSrcRange, Range("$A$1:$E$10"), , xlYes).name = "Table1" with targetRange.Worksheet.ListObjects.Add(xlSrcRange, targetRange, , xlYes).name = tableName. Every range is associated with a worksheet, so we can retrieve this worksheet using targetRange.Worksheet instead of using ActiveSheet.
  • Replaced Range("Table1[#All]").Select with targetRange.Worksheet.ListObjects(tableName).TableStyle = "TableStyleMedium1.
Listing 17.7: Refined version of the recorded macro in VBA. The refined macro formats a table in Excel by selecting a range, creating a table, and applying a specific style. The range and table name are passed as parameters to the Sub-Procedure for flexibility and reusability. The table name FormatedTable is used to create the table (you can see this name in the Excel sheet at the top left corner of the table).
'Modified version where the table range and name are parameters
Sub FormatRangeAsTable(targetRange As Range, tableName As String)   
    targetRange.Worksheet.ListObjects.Add(xlSrcRange, targetRange, , xlYes).name = tableName
    targetRange.Worksheet.ListObjects(tableName).TableStyle = "TableStyleMedium1"
End Sub

'Sub to test the procedure `FormatRangeAsTable` passing a range and a table name.
Sub ExampleFormatRangeAsTable()
    FormatRangeAsTable Range("$A$13:$E$23"), "FormatedTable"
End Sub

To test the refined macro, you can run the Sub-Procedure ExampleFormatRangeAsTable from the VBA editor. This Sub-Procedure calls the FormatRangeAsTable procedure, passing the range $A$13:$E$23 and the table name "FormatedTable". This new range contains a copy of the original data, so you can test the formatting without affecting the original table.

17.3 Variable Scope

The scope of a variable determines where in the code it can be accessed and modified.

Besides Dim, and Const, you can also declare variables using the following keywords:

  • Static:
    • Variables declared with Static within a procedure retain their values between procedure calls.
  • Public:
    • Variables declared with Public at the “Declarations” section (at the top of the module, before the first Sub/Function statement) have global scope.
    • Procedures declared with Public or not declared with any scope keyword (i.e., simply Sub or Function) can be accessed from other modules.
  • Private:
    • Variables declared with Private at the “Declarations” section have module scope (can only be accessed within the module).
    • Variables declared without any scope keyword (i.e., simply Dim) at the “Declarations” section have module scope.
    • Procedures declared with Private (e.g., Private Sub or Private Function) have module scope.
Resetting Variables

To reset Public, Private, or Static variables, you have to reset (click the square stop button) the VBA editor or erase the variables manually.

In Listing 17.8, we have an example of variable scopes in VBA. It simulates an airline ticket counter selling tickets for Economy and Business classes. There are a total of 20 tickets available, with 10% of them allocated to the Business class. For each customer arriving at the counter, a random number is generated to determine if they will be assigned to the Economy or Business class. If there are available seats in the chosen class, the customer is added to the class; otherwise, a message is displayed indicating that no seats are available. The experiment is repeated until all tickets are sold.

The code consists of four modules:

  • TicketCounter: Contains the main procedure Main that adds customers to the Economy or Business class and generates a table in Excel (see Listing 17.8 (a)).
  • EconomyClass: Contains the procedures to add customers to the Economy class and clear the customers (see Listing 17.8 (b)).
  • BusinessClass: Contains the procedures to add customers to the Business class and clear the customers (see Listing 17.8 (c)).
  • CustomerReport: Contains the procedure to print the customer data for the Economy and Business classes (see Listing 17.8 (d)).

When executing the procedure Main, the following steps are performed:

  1. The passengerCount is reset to 0, the passengers array is cleared, and the customer lists for the Economy and Business classes are cleared.
  2. The ticket sales simulation is performed until all tickets are sold.
    1. A random number is generated to determine if the customer will be assigned to the Economy or Business class.
    2. If there are available seats in the chosen class, the customer is added to the class.
    3. The customer data is printed.
  3. The passenger data is generated in an Excel table.
Debug the Simulation

Starting from the Main procedure, you can debug the simulation by setting breakpoints, stepping through the code, and observing the changes in the variables and customer lists. Make sure to check the output in the Immediate Window to track the progress of the simulation and the Locals Window to inspect the values of variables. Pay attention to how the code uses global, public, and private variables to store and manage passenger data.

Listing 17.8: Example of variable scopes in VBA. The code consists of four modules: TicketCounter, EconomyClass, BusinessClass, and CustomerReport.
(a) Module “Main”. The variables passengers and nPassengers are declared with global scope. Given nCustomers customers, the procedure Main adds customers to the Economy or Business class and generates a table in Excel. The procedure Main uses these variables to store passenger data and generate a table in Excel.
Option Explicit

Public passengers() As Variant
Dim passengerCount As Integer
Public Const TOTAL_TICKETS As Integer = 20
Public Const BUSINESS_PROB As Double = 0.3
Public Const BUSINESS_SEAT_PERCENTAGE As Double = 0.1

Function CanAddPassenger( _
        ByVal currentCount As Integer, _
        ByVal maxLimit As Integer) As Boolean
    If currentCount >= maxLimit Then
        CanAddPassenger = False
    Else
        CanAddPassenger = True
    End If
End Function

Function GetMaxSeats(isBusinessClass As Boolean) As Integer
    If isBusinessClass Then
        GetMaxSeats = BUSINESS_SEAT_PERCENTAGE * TOTAL_TICKETS
    Else
        GetMaxSeats = (1 - BUSINESS_SEAT_PERCENTAGE) * TOTAL_TICKETS
    End If
End Function

Sub AddPassenger(ByVal name As String, ByVal typeCustomer As String)

    passengerCount = passengerCount + 1
    ReDim Preserve passengers(1 To 2, 1 To passengerCount)
    passengers(1, passengerCount) = name
    passengers(2, passengerCount) = typeCustomer

End Sub

Sub SimulateTicketSales()
    
    Dim trialCount As Integer
    Dim ticketSold As Integer
    Dim customerName As String
    
    ClearPassengers
    trialCount = 0
    ticketSold = 0

    Do While ticketSold < TOTAL_TICKETS

        trialCount = trialCount + 1
        customerName = "P" & trialCount
        Debug.Print "## At the counter: " & customerName

        If Rnd() < BUSINESS_PROB Then
            If CanAddPassenger( _
                    BusinessClass.businessCustomerCount, _
                    GetMaxSeats(True)) Then
                
                BusinessClass.AddCustomer customerName
                ticketSold = ticketSold + 1
            Else
                Debug.Print "No Business seats available!"
            End If
        Else
            If CanAddPassenger( _
                    EconomyClass.economyCustomerCount, _
                    GetMaxSeats(False)) Then
        
                EconomyClass.AddCustomer customerName
                ticketSold = ticketSold + 1
            Else
                Debug.Print "No Economy seats available!"
            End If
        End If
        
        CustomerReport.PrintCustomers
    Loop

End Sub

Sub GeneratePassengerTable()
    Cells(1, 1) = "Passenger"
    Cells(1, 2) = "Class"

    Dim i As Integer
    For i = LBound(passengers, 2) To UBound(passengers, 2)
        Cells(i + 1, 1) = passengers(1, i)
        Cells(i + 1, 2) = passengers(2, i)
    Next i
End Sub

Sub ClearPassengers()
    Range("A1:B" & passengerCount + 1).ClearContents
    Erase passengers
    passengerCount = 0
    BusinessClass.ClearCustomers
    EconomyClass.ClearCustomers
End Sub

Sub Main()
    Call ClearPassengers
    Call SimulateTicketSales
    Call GeneratePassengerTable
End Sub
(b) Module “EconomyClass”. The variables economyCustomerCount and economyCustomers are declared with module and public scope, respectively. The procedure AddCustomer adds a customer to the economy class and increments the public variable economyCustomerCount. The procedure PrintCustomers prints the customer data for the Economy class and the procedure ClearCustomers clears the customers from the Economy class.
Option Explicit

Public economyCustomerCount As Integer
Dim economyCustomers() As String
Private Const PASSENGER_TYPE As String = "Economy"

Sub AddCustomer(ByVal customerName As String)
    economyCustomerCount = economyCustomerCount + 1
    ReDim Preserve economyCustomers(1 To economyCustomerCount)
    economyCustomers(economyCustomerCount) = customerName
    AddPassenger customerName, PASSENGER_TYPE
    Debug.Print "Economy Customer Added: " & customerName
    Debug.Print "Total Economy Customers: " & economyCustomerCount
End Sub

Sub ClearCustomers()
    Erase economyCustomers
    economyCustomerCount = 0
End Sub


Sub PrintCustomers()

    Debug.Print "=== Economy Class Customers ==="
    Dim i As Integer
    For i = 1 To economyCustomerCount
        Debug.Print "Economy Customer " & i & ": " & economyCustomers(i)
    Next i
End Sub
(c) Module “BusinessClass”. The variables businessCustomerCount and businessCustomers are declared with module and public scope, respectively. The procedure AddCustomer adds a customer to the business class and increments the private variable businessCustomerCount. The procedure PrintCustomers prints the customer data for the Business class and the procedure ClearCustomers clears the customers from the Business class.
Option Explicit

Public businessCustomerCount As Integer
Dim businessCustomers() As String
Private Const PASSENGER_TYPE As String = "Business"

Sub AddCustomer(ByVal customerName As String)
    businessCustomerCount = businessCustomerCount + 1
    ReDim Preserve businessCustomers(1 To businessCustomerCount)
    businessCustomers(businessCustomerCount) = customerName
    AddPassenger customerName, PASSENGER_TYPE
    Debug.Print "Business Customer Added: " & customerName
    Debug.Print "Total Business Customers: " & businessCustomerCount
End Sub

Sub ClearCustomers()
    Erase businessCustomers
    businessCustomerCount = 0
End Sub


Sub PrintCustomers()

    Debug.Print "=== Business Class Customers ==="
    Dim i As Integer
    For i = 1 To businessCustomerCount
        Debug.Print "Business Customer " & i & ": " & businessCustomers(i)
    Next i
End Sub
(d) Module “CustomerReport”. The procedure PrintCustomers prints the customer data for the Economy and Business classes. The variable reportCount is declared with static scope. Hence, across multiple calls to PrintCustomers from the SimulateTicketSales procedure, the variable retains its value.
Option Explicit

Sub PrintCustomers()
    Static reportCount As Long
    reportCount = reportCount + 1
    
    Debug.Print "###### Report " & reportCount

    ' Call the individual PrintCustomers from each class
    EconomyClass.PrintCustomers
    BusinessClass.PrintCustomers

End Sub

17.4 Exercises

17.4.1 Avoiding Duplicate Reads

Create a Sub-Procedure ReadDataFromSpreadsheet that reads the table Table 17.1 and saves the values in a public array called customerData. Ensure that, even if this Sub-Procedure is called multiple times, it only reads the values once.

Why Doing This?

Reading large datasets from a spreadsheet can be time-consuming. If you need to access the data multiple times in your VBA code, it is more efficient to read the data once and store it in an array.

17.4.2 Matrix Swap

Create a function SwapValuesMatrices that receives two matrices with equal dimensions and swaps their values. The values inside the matrices should be swapped element by element. Next, create a subprocedure to test your function.

17.4.3 Scope Analysis

Regarding the example shown in Listing 17.8:

  • What is the scope of the variable passengerCount? Can it be accessed from the EconomyClass and BusinessClass modules?
  • What is the scope of the variable economyCustomerCount? Can it be accessed from the BusinessClass module? Can it be accessed from the TicketCounter module?
  • What is the scope of the variable businessCustomerCount? Can it be accessed from the EconomyClass module? Can it be accessed from the TicketCounter module?
  • What is the scope of the variable passengers? Can it be accessed from the EconomyClass and BusinessClass modules?
  • What is the scope of the variable economyCustomers? Can it be accessed from the BusinessClass module? Can it be accessed from the TicketCounter module?
  • After two simulation runs:
    • What is the minimum value of reportCount in the CustomerReport module?
    • What is the size of the passengers array in the TicketCounter module?
    • What is the size of the economyCustomers array in the EconomyClass module?
    • What is the size of the businessCustomers array in the BusinessClass module?