Skip to content

Unit Testing

Tom edited this page Nov 20, 2022 · 25 revisions

Test Explorer

The Test Explorer allows browsing/finding, running, and adding unit tests to the active VBProject:

Test Explorer window

QuickStart

The Refresh command synchronizes the test methods with the code in the IDE, but if test methods are added from within the Test Explorer then the new tests will appear automatically.

The Run menu makes running the tests as convenient as in the .NET versions of Visual Studio:

Test Explorer 'Run' menu

"Selected Tests" refer to the selection in the grid, not in the IDE.

The Add menu makes it easy to add new tests:

Test Explorer 'Add' menu

Adding a Test Module ensures the active VBProject has a reference to the add-in's type library, then adds a new standard code module with this content:

'@TestModule
'@Folder("Tests")
Option Explicit
Private Assert As New Rubberduck.AssertClass
Private Fakes As Rubberduck.FakesProvider

Adding a Test Method adds this template snippet at the end of the active test module:

'@TestMethod
Public Sub TestMethod1() 'TODO: Rename test
    On Error GoTo TestFail

    'Arrange

    'Act

    'Assert
    Assert.Inconclusive
    
TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

Adding a Test Method (expected error) adds this template snippet at the end of the active test module:

'@TestMethod
Public Sub TestMethod2() 'TODO: Rename test
    Const ExpectedError As Long = 0 'TODO: Change to expected error number
    On Error GoTo TestFail
    
    'Arrange

    'Act

    'Assert
    Assert.Fail "Expected error was not raised."
    
TestExit:
    Exit Sub
TestFail:
    If Err.Number = ExpectedError Then
        Resume TestExit
    Else
        Resume Assert
    End If
End Sub

The number at the end of the generated method name depends on the number of test methods in the test module.

The Assert Class

Note: equality checks are made per the equality rules of C#, which is more strict than VBA. Implicit type conversions are not allowed, and strings are case-sensitive; this is by design. A PermissiveAssertClass implementation is on the roadmap, to allow more VBA-like equality checks.

The AssertClass type exposes the following members.

Name Description
AreEqual
Verifies that two specified objects are equal. The assertion fails if the objects are not equal.
AreNotEqual
Verifies that two specified objects are not equal. The assertion fails if the objects are equal.
AreNotSame
Verifies that two specified object variables refer to different objects. The assertion fails if they refer to the same object.
AreSame
Verifies that two specified object variables refer to the same object. The assertion fails if they refer to different objects.
Fail
Fails the assertion without checking any conditions.
Inconclusive
Indicates that the assertion cannot be verified.
IsFalse
Verifies that the specified condition is false. The assertion fails if the condition is true.
IsNothing
Verifies that the specified object is Nothing. The assertion fails if it is not Nothing.
IsNotNothing
Verifies that the specified object is not Nothing. The assertion fails if it is Nothing.
IsTrue
Verifies that the specified condition is true. The assertion fails if the condition is false.
NotSequenceEquals
Verifies that at least one of the items in 2 arrays(2D) differs at any give index. The assertion fails if all of the items are the same, if the lower bounds and upper bounds are the same, and the ranks (number of dimensions) are the same.
SequenceEquals
Verifies that all of the items in 2 arrays(2D) are equal. The assertion fails if any items is different, if either the lower bounds or upper bounds are different, or if the ranks (number of dimensions) differ.
Succeed
Passes the assertion without checking any conditions.

Discovery

Rubberduck will only attempt to find test methods in standard code modules (.bas) that have a '@TestModule marker comment.

Test methods must be Public, parameterless procedures (Sub). Public parameterless procedures in a test module will only be considered as test methods when their signature is immediately preceded by a '@TestMethod marker comment:

'@TestMethod
Public Sub TestSomething()

End Sub

AssertsClass Example

Say we needed to implement some NumKeyValidator object whose responsibility would be to validate the ASCII code for a pressed key, given the content of a textbox - we could specify it as follows:

  • Numeric values 0-9 are accepted
  • A dot is only valid when value doesn't already contain a dot

With Rubberduck we can implement that object in a test-driven manner - tests first! Of course we can't run the tests if the project won't compile, so we'll create a NumKeyValidator class and a method signature:

Option Explicit

Public Function IsValidKey(ByVal keyAscii As Integer, ByVal value As String) As Boolean
End Function

And then we can start writing a failing test:

Numeric values 0-9 are accepted

'@TestMethod
Public Sub AcceptsNumericKeys()
    On Error GoTo TestFail
    
    'Arrange:
    Dim value As String
    value = vbNullString
    
    Dim sut As NumKeyValidator 'sut denotes SystemUnderTest
    set sut = new NumKeyValidator

    'Act:
    'Assert:
    Dim i As Integer
    Dim testResult as Boolean
    For i = 0 To 9
        testResult = sut.IsValidKey(Asc(CStr(i)), value)
        If Not testResult Then GoTo TestExit ' Exit if any test fails
    Next
    
TestExit:
    Assert.IsTrue testResult, "Value '" & i & "' was not accepted."
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

To run the test, refresh the Test Explorer UI then select the test and press 'Run'. (Note: executing the TestMethod Sub won't actually run the test).

Let's make that test pass:

Option Explicit

Public Function IsValidKey(ByVal keyAscii As Integer, ByVal value As String) As Boolean
    IsValidKey = keyAscii >= KeyCodeConstants.vbKey0 And keyAscii <= KeyCodeConstants.vbKey9
End Function

Good. Now let's move on to the next requirement:

A dot is only valid when value doesn't already contain a dot

'@TestMethod
Public Sub AcceptsDotWhenValueHasNoDot()
    On Error GoTo TestFail
    
    'Arrange:
    Dim value As String
    value = "123"
    
    Dim sut As NumKeyValidator 'sut denotes SystemUnderTest
    Set sut = new NumKeyValidator

    Dim actual As Boolean
    
    'Act:
    actual = sut.IsValidKey(Asc("."), value)

    'Assert:
    Assert.IsTrue actual
    

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

That's still a very simple example, but it's a better example of what an Arrange-Act-Assert test should look like. The code that makes this test pass could look like this:

Private Const vbKeyDot As Long = 46
Option Explicit

Public Function IsValidKey(ByVal keyAscii As Integer, ByVal value As String) As Boolean
    IsValidKey = (keyAscii >= KeyCodeConstants.vbKey0 And keyAscii <= KeyCodeConstants.vbKey9) _
              Or (InStr(1, value, Chr$(vbKeyDot)) = 0 And keyAscii = vbKeyDot)
End Function

And now we fulfill the current requirements. If the requirements ever need to change, we can add more tests to document them, and we can modify the implementation knowing that if we introduce a bug, a test will fail.


Of course that's a simplified example that doesn't fully illustrate everything the Assert class can do. But starting with Assert.IsTrue and Assert.IsFalse is a good start; more complex logic might call for comparing expected and actual values - that's where Assert.AreEqual comes into play. Or you may need to test that a method returns a specific instance of an object - Assert.AreSame will pass if two objects have the same reference.

Sometimes you may need to raise an error when arguments are invalid - Rubberduck has a special test template for that, that will fail the test when a specific error number isn't raised by the method you're testing.

Keep your tests focused and to the point, make few assertions (or if you make a bunch, make sure they're closely related), and make sure your tests fail when they're supposed to fail, and you'll have a powerful maintenance tool in your hands.


Troubleshooting

Error 91 Object variable or with block not set:

The assert class will not run directly from the test method; instead run your test from the Rubberduck 'Test Explorer' UI.

The Fakes Class

Rubberduck can override calls to various VBA functions and statements while a test runs to provide the ability to test parts of your code that would otherwise be difficult to test in a suitable way. For example, you could test:

  • A sub that displays a message box to users by preventing the display and setting the return value of the MsgBox call to indicate that a particular button was pressed
  • A function that calculates a random number by setting a fixed return value of the Rnd function
  • Code that depends on the time of day by setting an exact time to be returned by the Time function

The fakes class exposes the following methods... (note that the Returns and ReturnsWhen methods only apply to functions, trying to use them on faked statements will cause an error).

Each FakesClass type exposes the following members.

Name Description
PassThrough
Set to true by default so that execution is handled by Rubberduck. Set it to False if you don't want to use the fake instance to block the native procedure but still want to be able to track invocations via the Verify methods below.
Note that some functions don't allow passthrough functionality as it would break the testing functionality e.g. display of a messagebox. The result of such a test will be set to inconclusive by Rubberduck if PassThrough is set to True.
Returns
Configures the fake such that the specified invocation returns the provided value. It takes the following parameters:
"Value": Value to be returned by the faked function.
"Invocation": An optional value for the specific invocation to return the Value for e.g. 1 for first invocation only. If not specified, the Value will be returned for all invocations unless overridden by another call to Returns or ReturnsWhen.
ReturnsWhen
Configures the fake such that the specified invocation returns the specified value given a specific parameter value. It takes the following parameters:
"Parameter": Name of the parameter to check for.
"Argument": Value to check the argument passed to the parameter.
"Value": Value to be returned by the faked function.
"Invocation": An optional value for the specific invocation to return the Value for e.g. 1 for first invocation only. If not specified, the Value will be returned for all invocations unless overridden by another call to Returns or ReturnsWhen.
RaisesError
Configures the fake such that the invocation raises the specified run-time error. It takes the following parameters:
"Number": Integer value to set for the error number.
"Description": String value to set for the error description.
Verify.AtLeast
Verifies that the faked procedure was called a minimum number of times. It takes the following parameters:
"Invocations": Expected minimum number of invocations.
"Message": An optional message to display if the verification fails.
Verify.AtLeastOnce
Verifies that the faked procedure was called one or more times. It takes the following parameters:
"Message": An optional message to display if the verification fails.
Verify.AtMost
Verifies that the faked procedure was called a maximum number of times. It takes the following parameters:
"Invocations": Expected maximum number of invocations.
"Message": An optional message to display if the verification fails.
Verify.AtMostOnce
Verifies that the faked procedure was not called or was only called once. It takes the following parameters:
"Message": An optional message to display if the verification fails.
Verify.Between
Verifies that number of times the faked procedure was called falls within the supplied range. It takes the following parameters:
"Minimum": Expected minimum invocations.
"Maximum": Expected maximum invocations.
"Message": An optional message to display if the verification fails.
Verify.Exactly
Verifies that the faked procedure was called a specific number of times. It takes the following parameters:
"Invocations": Expected number of invocations.
"Message": An optional message to display if the verification fails.
Verify.Never
Verifies that the faked procedure is never called. It takes the following parameters:
"Message": An optional message to display if the verification fails.
Verify.Once
Verifies that the faked procedure is called exactly one time. It takes the following parameters:
"Message": An optional message to display if the verification fails.
Verify.Parameter
Verifies that a given parameter to the faked procedure matches a specific value. It takes the following parameters:
"Parameter": The name of the parameter to verify. Case insensitive.
"Value": The expected value of the parameter.
"Invocation": The invocation to test against. Optional - defaults to the first invocation.
"Message": An optional message to display if the verification fails.
Verify.ParameterInRange
Verifies that the value of a given parameter to the faked procedure falls within a specified range. It takes the following parameters:
"Parameter": The name of the parameter to verify. Case insensitive.
"Minimum": The minimum expected value of the parameter.
"Maximum": The maximum expected value of the parameter.
"Invocation": The invocation to test against. Optional - defaults to the first invocation.
"Message": An optional message to display if the verification fails.
Verify.ParameterIsPassed
Verifies that an optional parameter was passed to the faked procedure. The value is not evaluated. It takes the following parameters:
"Parameter": The name of the parameter to verify. Case insensitive.
"Invocation": The invocation to test against. Optional - defaults to the first invocation.
"Message": An optional message to display if the verification fails.
Verify.ParameterIsType
VerifieVerifies that the passed value of a given parameter is of a given type. It takes the following parameters:
"Parameter": The name of the parameter to verify. Case insensitive.
"TypeName": The expected type as it would be returned by VBA.TypeName. Case insensitive.
"Invocation": The invocation to test against. Optional - defaults to the first invocation.
"Message": An optional message to display if the verification fails.

The following VBA functions and statements can currently be faked:

Interaction

  • MsgBox
  • InputBox
  • Timer
  • Beep
  • DoEvents
  • DeleteSetting
  • SaveSetting
  • GetSetting
  • GetAllSettings
  • IMEStatus
  • Environ
  • SendKeys
  • Shell

File system

  • Kill
  • MkDir
  • RmDir
  • ChDir
  • ChDrive
  • CurDir
  • GetAttr
  • SetAttr
  • FileLen
  • FileDateTime
  • FreeFile
  • Dir
  • FileCopy

Math

  • Rnd
  • Randomize

System

  • Now
  • Date
  • Time

More may be added over time. The up-to-date list of fakes items can be found by visiting the tracking issue #2891

FakesClass Example

In these examples we will set fakes for code that is inside the test method. In practice, the test method would be calling existing procedures within your code base. It is the calls within those procedures that get faked, allowing you the ability to test more code that would otherwise be the case.

Example preventing MsgBox display

Taken from Rubberduck News. MsgBox is called but instead of displaying an actual messagebox requiring user interaction, the call is logged and a return value set for for the MsgBox function so that code will continue uninterrupted.

'@TestMethod
Public Sub TestMethod1()
    On Error GoTo TestFail
    
    Fakes.MsgBox.Returns 42
    Debug.Print MsgBox("Flabbergasted yet?", vbYesNo, "Rubberduck") 'prints 42
    
    With Fakes.MsgBox.Verify
        .Parameter "prompt", "Flabbergasted yet?"
        .Parameter "buttons", vbYesNo
        .Parameter "title", "Rubberduck"
    End With
TestExit: 
    Exit Sub
TestFail: 
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

In general it is best to test small amounts of code. In theory you can set up fakes for multiple VBA procedures but there is a risk of issues due to interactions between them. If unexpected behaviour occurs, try simplifying the system under test.

Clone this wiki locally