20  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).

WarningDefault 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).

20.1 Passing Variables

In Listing 20.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 20.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 20.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 20.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 20.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 20.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

20.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 20.4.

Listing 20.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 20.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 20.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