Coder Social home page Coder Social logo

vba-test's Introduction

vba-test

vba-test (formerly Excel-TDD and VBA-TDD) adds testing to VBA on Windows and Mac.

Donate

Example

Function AddTests() As TestSuite
  Set AddTests = New TestSuite
  AddTests.Description = "Add"

  ' Report results to the Immediate Window
  ' (ctrl + g or View > Immediate Window)
  Dim Reporter As New ImmediateReporter
  Reporter.ListenTo AddTests

  With AddTests.Test("should add two numbers")
    .IsEqual Add(2, 2), 4
    .IsEqual Add(3, -1), 2
    .IsEqual Add(-1, -2), -3
  End With

  With AddTests.Test("should add any number of numbers")
    .IsEqual Add(1, 2, 3), 6
    .IsEqual Add(1, 2, 3, 4), 10
  End With
End Function

Public Function Add(ParamArray Values() As Variant) As Double
  Dim i As Integer
  Add = 0
  
  For i = LBound(Values) To UBound(Values)
    Add = Add + Values(i)
  Next i
End Function

' Immediate Window:
'
' === Add ===
' + should add two numbers
' + should add any number of numbers
' = PASS (2 of 2 passed) =

For details of the process of reaching this example, see the TDD Example

Advanced Example

For an advanced example of what is possible with vba-test, check out the tests for VBA-Web

Getting Started

  1. Download the latest release (v2.0.0-beta.3)
  2. Add src/TestSuite.cls, src/TestCase.cls, add src/ImmediateReporter.cls to your project
  3. If you're starting from scratch with Excel, you can use vba-test-blank.xlsm

If you're updating from Excel-TDD v1, follow these upgrade details.

TestSuite

A test suite groups tests together, runs test hooks for actions that should be run before and after tests, and is responsible for passing test results to reporters.

' Create a new test suite
Dim Suite As New TestSuite
Suite.Description = "Module Name"

' Create a new test
Dim Test As TestCase
Set Test = Suite.Test("Test Name")
Test.IsEqual ' ...

' or create and use test using With
With Suite.Test("Test Name")
  .IsEqual '...
End With

TestSuite API

  • Description
  • Test(Name) As TestCase
  • Event BeforeEach(Test)
  • Event Result(Test)
  • Event AfterEach(Test)

TestCase

A test case uses assertions to test a specific part of your application.

With Suite.Test("specific part of your application")
  .IsEqual A, B, "(optional message, e.g. result should be 12)"
  .NotEqual B, C

  .IsOk C > B
  .NotOk B > C

  .IsUndefined ' Checks Nothing, Empty, Missing, or Null
  .NotUndefined

  .Includes Array(1, 2, 3), 2
  .NotIncludes Array(1, 2, 3), 4
  .IsApproximate 1.001, 1.002, 2
  .NotApproximate 1.001, 1.009, 3
  
  On Error Resume Next
  
  Err.Raise vbObjectError + 1, Description:="Uh oh."
  .IsError Description:="Uh oh."
  
  Err.Clear
  .NotError

  .Pass
  .Fail "e.g. should not have gotten here" 
  .Plan 4 ' Should only be 4 assertions, more or less fails
  .Skip ' skip this test
End With

With Suite.Test("complex things")
  .IsEqual _
    ThisWorkbook.Sheets("Hidden").Visible, _
    XlSheetVisibility.xlSheetVisible
  .IsEqual _
    ThisWorkbook.Sheets("Main").Cells(1, 1).Interior.Color, _
    RGB(255, 0, 0)
End With

In addition to these basic assertions, custom assertions can be made by passing the TestCase to an assertion function

Sub ToBeWithin(Test As TestCase, Value As Variant, Min As Variant, Max As Variant)
  Dim Message As String
  Message = "Expected " & Value & " to be within " & Min & " and " & Max

  Test.IsOk Value >= Min, Message
  Test.IsOk Value <= Max, Message
End Sub

With Suite.Test("...")
  ToBeWithin(.Self, Value, 0, 100)
End With

TestCase API

  • Test.Name
  • Test.Self - Reference to test case (useful inside of With)
  • Test.Context - Dictionary holding test context (useful for BeforeEach/AfterEach)
  • Test.IsEqual(A, B, [Message])
  • Test.NotEqual(A, B, [Message])
  • Test.IsOk(Value, [Message])
  • Test.NotOk(Value, [Message])
  • Test.IsUndefined(Value, [Message])
  • Test.NotUndefined(Value, [Message])
  • Test.Includes(Values, Value, [Message]) - Check if value is included in array or Collection
  • Test.NotIncludes(Values, Value, [Message])
  • Test.IsApproximate(A, B, SignificantFigures, [Message]) - Check if two values are close to each other (useful for Double values)
  • Test.NotApproximate(A, B, SignificantFigures, [Message])
  • Test.IsError([Number], [Source], [Description], [Message]) - Check if Err contains an error
  • Test.NotError([Message])
  • Test.Pass() - Explicitly pass the test
  • Test.Fail([Message]) - Explicitly fail the test
  • Test.Plan(Count) - For tests with loops and branches, it is important to catch if any assertions are skipped or extra
  • Test.Skip() - Notify suite to skip this test

ImmediateReporter

With your tests defined, the easiest way to display the test results is with ImmediateReporter. This outputs results to the Immediate Window (ctrl+g or View > Immediate Window) and is useful for running your tests without leaving the VBA editor.

Public Function Suite As TestSuite
  Set Suite = New TestSuite
  Suite.Description = "..."

  ' Create reporter and attach it to these specs
  Dim Reporter As New ImmediateReporter
  Reporter.ListenTo Suite

  ' -> Reporter will now output results as they are generated
End Function

Context / Lifecycle Hooks

TestSuite includes events for setup and teardown before tests and a Context object for passing values into tests that are properly torn down between tests.

' Class TestFixture
Private WithEvents pSuite As TestSuite

Public Sub ListenTo(Suite As TestSuite)
  Set pSuite = Suite
End Sub

Private Sub pSuite_BeforeEach(Test As TestCase)
  Test.Context.Add "fixture", New Collection
End Sub

Private Sub pSuite_AfterEach(Test As TestCase)
  ' Context is cleared automatically,
  ' but can manually cleanup here
End Sub

' Elsewhere

Dim Suite As New TestSuite

Dim Fixture As New TestFixture
Fixture.ListenTo Suite

With Suite.Test("...")
  .Context("fixture").Add "..."
End With

vba-test's People

Contributors

joyfullservice avatar kanayama-acn avatar sdaves avatar timhall avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

vba-test's Issues

TestFixture() class as part of block?

Class events in VBA is kind of a pain

The only way it seems to execute the before, after, and Result events of the TestSuite seems to be through the TestFixture() described in the README, and used in many other VBA-Tools implementations.

Why isn't TestFixture() distributed in ./src/?

spy/mocks?

Is this on the roadmap? If not do you know a way to manually mock out a function to check if it returns or to force a return value, etc?

Which documentation generator do you use?

Tim, dumb question, but I don't know for sure. I see a lot of documentation generators online that support VB/VBA (more or less), and I don't see a note in the repo or Wiki that tells me.

Context: I am writing a new reporter to support a multi-file test runner, and I would like to make sure I am consistent with what your documentation generator expects.

Thanks!

Plan: Update runners

Tasks:

  • Move runner calculations to SpecSuite
  • Integrate inline runner into SpecSuite as SpecSuite.(Print, Results, Debug, etc.)
  • Make display runner prettier: Progress, clearer failures and overall results, cleaner UI

Plan: Performance testing extension

Goal: Add performance tests to output of tests (wouldn't necessarily be pass/fail, just info).

Possible designs:

' Custom matcher
With Specs.It("speed test as custom matcher")
    .Expect("Callback").RunMatcher "SpeedTest"

    ' Pros: Callback can be called multiple times (for average speed)
    '       Uses currently available methods 
    ' Cons: Not the most intuitive API
End With

' Method that takes SpecDefinition and Callback
SpeedTest(Specs.It("speed test with definition and callback"), "Callback", Args...)

' Pros: Simple API, callback can be called multiple times
' Cons: More intuitive, but still not perfect

' Most likely design
' ------------------
' Run, Start, and Finish
SpeedTest.Run Specs, "speed test with Run", "Callback", Args...
SpeedTest.Start Specs, "speed test with Start and Finish"
' ...
SpeedTest.Finish

Fail suite for unhandled error

This is partially related to #24 perhaps, but it would be useful to support failing a suite if an unhandled error occurred. This may be difficult to accomplish automatically in VBA, so it may require some wrapping in the "RunTests" entry point.

This is mostly to help assist in running the full suite uninterrupted (e.g. CI/CD environments).

Possible memory leak?

Not sure if I am missing something here or if I uncovered a memory leak. I was adding a Terminate event to TestSuite and noticed it doesn't fire.

Private Sub Class_Terminate()
    Debug.Print "This should fire from TestSuite..."
    Stop
End Sub

I was trying to find out why this was being skipped over and I came across this rubberduck blog lazy-object-weak-reference.

By storing the TestCase objects in the Tests collection it seems like it stays in memory (possibly even all the TestCase objects as well then?). I don't know how to check if this actually is the case or if something else is going on preventing the event to fire.


I ran a test in which I set the collection to nothing and sure enough the Terminate event fires. Perhaps TestSuite should have it's own state of the various statuses of the tests vs holding references to all the TestCase classes?

Run Test Suite classes with method per test

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? ๐Ÿ˜„

SpecDefinition should return its own reference

It would be very helpful if SpecDefinition could return a reference to itself. For example:

With Specs.It("should be a good example")
    Set Foo = Bar.FooBarIt()
    VerifyIsAnObject(.Self, Foo)
End With

Private Function VerifyIsAnObject(ByRef SpecsIt As SpecDefinition, ByRef Foo As Bar)

    With SpecsIt
        .Expect(Foo...).ToBe...
    End With

End Function

While I understand RunMatcher exists, you may not want to make your various functions public. RunMatcher also doesn't support the fluent Expect().ToBe() syntax used throughout the rest of our suites.

Asserting Err Object

It would be useful to be able to assert the Err object and ensure that either no error occurred as expected, or that the expected error was called:

With Suite.Test("calling AcceptsLongsOnly with a long should not raise an error")
	On Error Resume Next
	Err.Clear
	MyModule.AcceptsLongsOnly 123
	.ToNotBeError Err
	On Error GoTo 0
End With

With Suite.Test("calling AcceptsLongsOnly with non-longs should raise an error")
	On Error Resume Next
	Err.Clear
	MyModule.AcceptsLongsOnly "ABC"
	.ToBeError Err, vbObjectError + 10001, "Expected value to be Long."
	On Error GoTo 0

	On Error Resume Next
	Err.Clear
	MyModule.AcceptsLongsOnly True
	.ToBeError Err, vbObjectError + 10001, "Expected value to be Long."
	On Error GoTo 0
End With

Of course, the naming of ToNotBeError and ToBeError are only examples. It may be possible to build them into IsOk and NotOk, but I'd prefer a dedicated method with Err or Error in the name for clarity.

Update Workbook proxy

Tasks:

  • Add AfterEach to teardown workbook after each test
  • Add instance to BeforeEach and AfterEach methods to allow passing in workbook helper instance
  • Separate from core into extensions (WBProxy and Scenario)
  • Use copy of workbook in case it's already open or unexpected things happen
  • Explore using standard WBProxy in other IWBProxy implementations. (lots of overlap currently)

BeforeEach and AfterEach goal:

Dim Proxy As New WBProxy
' Initial setup/mapping...

Suite.BeforeEach "Setup", Instance:=Proxy
Suite.AfterEach "Teardown", Instance:=Proxy

Causes an issue with current arguments implementation, since ParamArray cannot be used with other Optional variables (Instance), but ByRef with BeforeEach and AfterEach is a goal, so ParamArray might not be useful anyways.

Provide a 'toBeCloseTo' matcher for precision math comparison

Jasmine provides a 'toBeCloseTo' matcher for precision math comparison. It would be good for Excel-TDD to implement the same in SpecExpectation.cls.

This new feature would assist in the unit testing of probabilistic data structures and algorithms, such as Bloom filters.

Example usage

it("The 'toBeCloseTo' matcher is for precision math comparison", function() {
    var pi = 3.1415926,
      e = 2.78;

    expect(pi).not.toBeCloseTo(e, 2);
    expect(pi).toBeCloseTo(e, 0);
  });

Example Javascript implementation

getJasmineRequireObj().toBeCloseTo = function() {

  function toBeCloseTo() {
    return {
      compare: function(actual, expected, precision) {
        if (precision !== 0) {
          precision = precision || 2;
        }

        return {
          pass: Math.abs(expected - actual) < (Math.pow(10, -precision) / 2)
        };
      }
    };
  }

  return toBeCloseTo;
};

Note: There has been some discussion in the Jasmine community of the most appropriate API to provide, either by way of an inverse exponent or a simple tolerance level. Worth discussing.

WorkbookReporter should be able to create it's own output sheet

when assigning WorkbookReporter.ConnectTo(), it will attach to any worksheet.

if you try to run WorkbookReporter.Start() subsequently, a runtime error will occur if the sheet connected to does not contain specificly named ranges and shapes.

it would be great if Start() or Initialize() could do the following

  1. me.pSheet is null => create a new sheet with pretty report formatting and the required shapes and ranges
  2. me.pSheet does not contain each of the required named ranges or shapes => create these entities, or describe to the user why it can't continue, and how to fix it.

Need more explanatory examples

Its is nice to have the examples that are there, but I think there needs to be some written examples showing how to put it all together (as upposed to loading "VBB-TDD Specs.xlsm" and reverse engineering).

AfterEach

It would be great if AfterEach functionality existed to be symmetrical with BeforeEach.

Is this on the roadmap?

Function Examples end as Sub

There are at least two code examples in this project which are functions but end with "End Sub":

  • In Readme.md the function "Function AddTests() As TestSuite"
  • In the TDD example, the function "Public Function Specs() As SpecSuite"

This is a trivial issue, I know. It's a documentation issue really rather than a source code issue. But since the fix is also trivial I figured I might as well raise it.

Fix: Change "End Sub" to "End Function"

P.s. Thanks for the amazing test harness!

IsEqual does not support Array Types

IsEqual should support Array Types so that users can compare if two arrays are identical (same size, index 0 matches index 0, etc.). Currently it falls through to the else clause:

IsEqual = Actual = Expected

and causes a VB runtime error.

ArrayIncludes() cannot handle multi-dimension arrays

example test:

Tests.test("range should contain value").Includes myRange.value2, "myValue"

an error occurs because myRange.Value2 is a 2 dimensional array.

in ArrayIncludes(), called by Includes()
VBA.IsArray(Value(i)) causes an error if Value() is multidimensional

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.