15  Variable Scope

The scope of a variable determines where in the code it can be accessed and modified. When variables are declared using the Dim keyword within a procedure (Sub or Function), they have local scope. This means that these variables can only be accessed and modified within that specific procedure. Once the procedure ends, the local variables are erased from memory (it “dies”).

The Dim keyword can also be used at the “Declarations” section (at the top of the module, before the first Sub/Function statement). In this case, the variables have module scope, meaning they can be accessed by all procedures within that module, but not from other modules. It also dies when the workbook is closed or when the VBA editor is reset.

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

Figure 15.1 shows the hierarchy of variable scopes in VBA, from the broadest scope (Global) to the narrowest scope (Local).

Figure 15.1: Hierarchy of variable scopes in VBA.
WarningResetting 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.

Public and Private variables declared at the “Declarations” section can also be declared as Const to create global or module-level constants, respectively. For example:

Public Const PI As Double = 3.14159
Private Const MAX_SIZE As Integer = 100

15.1 Example: Static vs. Regular Local Variables

In the example below, we demonstrate the scope of variables in VBA. Both variables are only valid inside the Sub, however:

  • dimVar is erased from memory once the Sub ends
  • staticVar holds the value assigned to it before (can be used again next time Sub is called)

Therefore, staticVar retains its value across multiple calls to the Sub, while dimVar is reinitialized each time the Sub is called.

Listing 15.1: Procedure declareStatic declares a static variable staticVar and a regular local variable dimVar. When calling the procedure multiple times from testDeclareStatic, you can observe that staticVar retains its value across calls, while dimVar is reinitialized each time.
Option Explicit

Sub declareStatic(numCall As Integer, addValue As Double)
    
    Static staticVar As Double
    Dim dimVar As Double
    
    Debug.Print "Call"; numCall; " :- Value local variable:"; dimVar
    Debug.Print "Call"; numCall; " :- Value static variable:"; staticVar
    dimVar = dimVar + addValue
    staticVar = staticVar + addValue

End Sub

Sub testDeclareStatic()

    Debug.Print "Declaring static and regular variable..."
    
    Dim numCall As Integer
    
    'Call Sub declaring static variable 10X
    For numCall = 1 To 10
    
        Call declareStatic(numCall, 10)
    
    Next numCall
    
End Sub

15.2 Example: An Airline Ticket Counter Simulation

In Listing 15.2, 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 15.2 (a)).
  • EconomyClass: Contains the procedures to add customers to the Economy class and clear the customers (see Listing 15.2 (b)).
  • BusinessClass: Contains the procedures to add customers to the Business class and clear the customers (see Listing 15.2 (c)).
  • CustomerReport: Contains the procedure to print the customer data for the Economy and Business classes (see Listing 15.2 (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.
TipDebug 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 15.2: 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

15.3 Exercises

15.3.1 Avoiding Duplicate Reads

Create a Sub-Procedure ReadDataFromSpreadsheet that reads the table Table 12.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.

TipWhy 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.

15.3.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.

15.3.3 Scope Analysis

Regarding the example shown in Listing 15.2:

  • 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?