Skip to content

Run Test Suite classes with method per test #26

Open
@mistresseve666

Description

@mistresseve666

I really enjoy vba-tdd for it's simplicity, however, I find it limiting when developing large test suites. The fact that everything must be in a single function can either make for very long messy suites or create a ton of small suites. Splitting into sub-suites is also difficult due to VBA's module name size limitation. I've ran into the Procedure too large error several times so far too.

It would be helpful to support running test suite classes where each method is its own test; this will help with a number of things as I'll discuss below.

As an example, the AddTests example could be written as:

Option Explicit

Public Sub ShouldAddTwoNumbers(ByRef Test As TestCase)
    On Error GoTo UnexpectedError
    Test.IsEqual Add(2, 2), 4
    Test.IsEqual Add(3, -1), 2
    Test.IsEqual Add(-1, -2), -3
    On Error GoTo 0
    Exit Sub

    UnexpectedError:
    Test.FailFromError Err
End Sub

Public Sub ShouldAddAnyNumberOfNumbers(ByRef Test As TestCase)
    On Error GoTo UnexpectedError
    Test.IsEqual Add(1, 2, 3), 6
    Test.IsEqual Add(1, 2, 3, 4), 10
    On Error GoTo 0
    Exit Sub

UnexpectedError:
    Test.FailFromError Err
End Sub

Note: Technically error handling within the test subroutine would be optional; see below.

Because VBA does not support programmatically creating classes the user would have to specify a "factory method" to the reporter:

Public Function CreateTestCaseSuite() As Tests_TestCase
    Set CreateTestCaseSuite = New Tests_TestCase
End Function

Public Function CreateTestSuiteSuite() As Tests_TestSuite
    Set CreateTestSuiteSuite = New Tests_TestSuite
End Function

Public Sub RunTests()
    Dim Reporter As New WorkbookReporter
    Reporter.ConnectTo TestRunner
    
    Reporter.AddSuiteForFactory TestSuite.Create("TestCase"), "CreateTestCaseSuite"
    Reporter.AddSuiteForFactory TestSuite.Create("TestSuite"), "CreateTestSuiteSuite"
    Reporter.Done
End Sub

The reporter would be able to:

  1. Detect the suite's class name from the return type of the factory.
  2. Detect all Public Subroutines within the class.
  3. For each subroutine detected:
    1. Call the factory method to create a new instance.
    2. The name of each test can be extrapolated from the PascalCase/SnakeCase name of the test.
      e.g. ShouldAddTwoNumbers and should_add_two_numbers would both convert to "should add two numbers"
    3. Create a new TestCase for the TestSuite based on the above name.
    4. Call each subroutine while passing in the TestCase instance.

Note: To support class reuse SetUp/TearDown and SetUpSuite/TearDownSuite subroutines could be used.

This has several benefits:

  1. Allows for large test suites to be broken out into individual test subroutines.
  2. Ensures each test runs in a fresh context. You don't have to worry reusing variables that might affect the outcome of your test.
  3. Better error handling within the test itself.
  4. Provides global error handling for unhandled errors (when the Reporter calls CallByName it can detect if an error occured).
  5. Not having to worry about updating NumSuites.
  6. Provide the capability of timing how long each test and suite takes to run.
  7. Potentially support rerunning only failing suites/tests.

In order to make TestSuite.Create work the PredeclaredId would have to be set to True.

It may also be helpful to add a generic runner class instead of using the WorkbookReporter/ImmediateReporter directly:

Public Sub RunTests()
    Dim Runner As New TestSuiteRunner
    Runner.AddReporter WorkbookReporter.Create(ThisWorkbook.Worksheets("TestRunner"))
    Runner.AddReporter ImmediateReporter.Create() 
    
    Runner.AddSuiteForFactory TestSuite.Create("TestCase"), "CreateTestCaseSuite"
    Runner.AddSuiteForFactory TestSuite.Create("TestSuite"), "CreateTestSuiteSuite"

    Runner.Run
End Sub

Final closing notes: I bring this suggestion up because I really like the all-included aspect of vba-test. While there are more powerful solutions available for vba testing (like RubberDuck/SimplyVBUnit (with modification)), they require external installation which in my particular application is not a feasible option. I strongly feel such an enhancement to vba-test will make it much more flexible.

Thoughts? 😄

Metadata

Metadata

Assignees

No one assigned

    Labels

    No labels
    No labels

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions