-
Notifications
You must be signed in to change notification settings - Fork 301
Unit Testing
The Test Explorer allows browsing/finding, running, and adding unit tests to the active VBProject:
The Refresh command synchronizes the test methods with the code in the IDE, but if test methods are added from within the Text 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:
"Selected Tests" refer to the selection in the grid, not in the IDE.
The Add menu makes it easy to add new tests:
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
Option Explicit
Private Assert As New Rubberduck.AssertClass
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:
If Err.Number <> 0 Then
Assert.Fail "Test raised an error: " & Err.Description
End If
Resume TestExit
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:
Assert.AreEqual ExpectedError, Err.Number
Resume TestExit
End Sub
The number at the end of the generated method name depends on the number of test methods in the test module.
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.
|
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
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
For i = 0 To 9
Assert.IsTrue sut.IsValidKey(Asc(CStr(i)), value), "Value '" & i & "' was not accepted."
Next
TestExit:
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.
rubberduckvba.com
© 2014-2021 Rubberduck project contributors
- Contributing
- Build process
- Version bump
- Architecture Overview
- IoC Container
- Parser State
- The Parsing Process
- How to view parse tree
- UI Design Guidelines
- Strategies for managing COM object lifetime and release
- COM Registration
- Internal Codebase Analysis
- Projects & Workflow
- Adding other Host Applications
- Inspections XML-Doc
-
VBE Events