Skip to content

Commit d24eaf4

Browse files
authored
Merge pull request #23 from VBA-tools/vba-test
Refactor into vba-test
2 parents 304d2a8 + b15549b commit d24eaf4

17 files changed

+1190
-1296
lines changed

README.md

Lines changed: 156 additions & 126 deletions
Original file line numberDiff line numberDiff line change
@@ -1,41 +1,38 @@
1-
VBA-TDD
2-
=======
1+
# vba-test
32

4-
Bring the reliability of other programming realms to VBA with Test-Driven Development (TDD) for VBA on Windows and Mac.
3+
Add testing to VBA on Windows and Mac.
54

6-
Quick example:
5+
## Example
76

87
```vb
9-
Function Specs() As SpecSuite
10-
Set Specs = New SpecSuite
11-
Specs.Description = "Add"
12-
13-
' Report results to the Immediate Window
14-
' (ctrl + g or View > Immediate Window)
15-
Dim Reporter As New ImmediateReporter
16-
Reporter.ListenTo Specs
17-
18-
' Describe the desired behavior
19-
With Specs.It("should add two numbers")
20-
' Test the desired behavior
21-
.Expect(Add(2, 2)).ToEqual 4
22-
.Expect(Add(3, -1)).ToEqual 2
23-
.Expect(Add(-1, -2)).ToEqual -3
24-
End With
25-
26-
With Specs.It("should add any number of numbers")
27-
.Expect(Add(1, 2, 3)).ToEqual 6
28-
.Expect(Add(1, 2, 3, 4)).ToEqual 10
29-
End With
30-
End Function
8+
Function AddTests() As TestSuite
9+
Set AddTests = New TestSuite
10+
AddTests.Description = "Add"
11+
12+
' Report results to the Immediate Window
13+
' (ctrl + g or View > Immediate Window)
14+
Dim Reporter As New ImmediateReporter
15+
Reporter.ListenTo AddTests
16+
17+
With AddTests.Test("should add two numbers")
18+
.IsEqual Add(2, 2), 4
19+
.IsEqual Add(3, -1), 2
20+
.IsEqual Add(-1, -2), -3
21+
End With
22+
23+
With AddTests.Test("should add any number of numbers")
24+
.IsEqual Add(1, 2, 3), 6
25+
.IsEqual Add(1, 2, 3, 4), 10
26+
End With
27+
End Sub
3128

3229
Public Function Add(ParamArray Values() As Variant) As Double
33-
Dim i As Integer
34-
Add = 0
35-
36-
For i = LBound(Values) To UBound(Values)
37-
Add = Add + Values(i)
38-
Next i
30+
Dim i As Integer
31+
Add = 0
32+
33+
For i = LBound(Values) To UBound(Values)
34+
Add = Add + Values(i)
35+
Next i
3936
End Function
4037

4138
' Immediate Window:
@@ -48,131 +45,164 @@ End Function
4845

4946
For details of the process of reaching this example, see the [TDD Example](https://github.com/VBA-tools/VBA-TDD/wiki/TDD-Example)
5047

51-
### Advanced Example
48+
## Advanced Example
5249

53-
For an advanced example of what is possible with VBA-TDD, check out the [specs for VBA-Web](https://github.com/VBA-tools/VBA-Web/tree/master/specs)
50+
For an advanced example of what is possible with vba-test, check out the [tests for VBA-Web](https://github.com/VBA-tools/VBA-Web/tree/master/specs)
5451

55-
### Getting Started
52+
## Getting Started
5653

57-
1. Download the [latest release (v2.0.0-beta)](https://github.com/VBA-tools/VBA-TDD/releases)
58-
2. Add `src/SpecSuite.cls`, `src/SpecDefinition.cls`, `src/SpecExpectation.cls`, add `src/ImmediateReporter.cls` to your project
59-
3. If you're starting from scratch with Excel, you can use `VBA-TDD - Blank.xlsm`
54+
1. Download the [latest release (v2.0.0-beta.2)](https://github.com/vba-tools/vba-test/releases)
55+
2. Add `src/TestSuite.cls`, `src/TestCase.cls`, add `src/ImmediateReporter.cls` to your project
56+
3. If you're starting from scratch with Excel, you can use `vba-test-blank.xlsm`
6057

61-
### It and Expect
58+
## TestSuite
6259

63-
`It` is how you describe desired behavior and once a collection of specs is written, it should read like a list of requirements.
60+
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.
6461

6562
```vb
66-
With Specs.It("should allow user to continue if they are authorized and up-to-date")
67-
' ...
68-
End With
69-
70-
With Specs.It("should show an X when the user rolls a strike")
71-
' ...
63+
' Create a new test suite
64+
Dim Suite As New TestSuite
65+
Suite.Description = "Module Name"
66+
67+
' Create a new test
68+
Dim Test As TestCase
69+
Set Test = Suite.Test("Test Name")
70+
Test.IsEqual ' ...
71+
72+
' or create and use test using With
73+
With Suite.Test("Test Name")
74+
.IsEqual '...
7275
End With
7376
```
7477

75-
`Expect` is how you test desired behavior
78+
__TestSuite API__
79+
80+
- `Description`
81+
- `Test(Name) As TestCase`
82+
- _Event_ `BeforeEach(Test)`
83+
- _Event_ `Result(Test)`
84+
- _Event_ `AfterEach(Test)`
85+
86+
## TestCase
87+
88+
A test case uses assertions to test a specific part of your application.
7689

7790
```vb
78-
With Specs.It("should check values")
79-
.Expect(2 + 2).ToEqual 4
80-
.Expect(2 + 2).ToNotEqual 5
81-
.Expect(2 + 2).ToBeLessThan 7
82-
.Expect(2 + 2).ToBeLT 6
83-
.Expect(2 + 2).ToBeLessThanOrEqualTo 5
84-
.Expect(2 + 2).ToBeLTE 4
85-
.Expect(2 + 2).ToBeGreaterThan 1
86-
.Expect(2 + 2).ToBeGT 2
87-
.Expect(2 + 2).ToBeGreaterThanOrEqualTo 3
88-
.Expect(2 + 2).ToBeGTE 4
89-
.Expect(2 + 2).ToBeCloseTo 3.9, 0
91+
With Suite.Test("specific part of your application")
92+
.IsEqual A, B, "(optional message, e.g. result should be 12)"
93+
.NotEqual B, C
94+
95+
.IsOk C > B
96+
.NotOk B > C
97+
98+
.IsUndefined ' Checks Nothing, Empty, Missing, or Null
99+
.NotUndefined
100+
101+
.Includes Array(1, 2, 3), 2
102+
.NotIncludes Array(1, 2, 3), 4
103+
.IsApproximate 1.001, 1.002, 2
104+
.NotApproximate 1.001, 1.009, 3
105+
106+
.Pass
107+
.Fail "e.g. should not have gotten here"
108+
.Plan 4 ' Should only be 4 assertions, more or less fails
109+
.Skip ' skip this test
90110
End With
91111

92-
With Specs.It("should check Nothing, Empty, Missing, and Null")
93-
.Expect(Nothing).ToBeNothing
94-
.Expect(Empty).ToBeEmpty
95-
.Expect().ToBeMissing
96-
.Expect(Null).ToBeNull
97-
98-
' `ToBeUndefined` checks if it's Nothing or Empty or Missing or Null
99-
100-
.Expect(Nothing).ToBeUndefined
101-
.Expect(Empty).ToBeUndefined
102-
.Expect().ToBeUndefined
103-
.Expect(Null).ToBeUndefined
104-
105-
' Classes are undefined until they are instantiated
106-
Dim Sheet As Worksheet
107-
.Expect(Sheet).ToBeNothing
108-
109-
.Expect("Howdy!").ToNotBeUndefined
110-
.Expect(4).ToNotBeUndefined
111-
112-
Set Sheet = ThisWorkbook.Sheets(1)
113-
.Expect(Sheet).ToNotBeUndefined
112+
With Suite.Test("complex things")
113+
.IsEqual _
114+
ThisWorkbook.Sheets("Hidden").Visible, _
115+
XlSheetVisibility.xlSheetVisible
116+
.IsEqual _
117+
ThisWorkbook.Sheets("Main").Cells(1, 1).Interior.Color, _
118+
RGB(255, 0, 0)
114119
End With
120+
```
121+
122+
In addition to these basic assertions, custom assertions can be made by passing the `TestCase` to an assertion function
123+
124+
```vb
125+
Sub ToBeWithin(Test As TestCase, Value As Variant, Min As Variant, Max As Variant)
126+
Dim Message As String
127+
Message = "Expected " & Value & " to be within " & Min & " and " & Max
128+
129+
Test.IsOk Value >= Min, Message
130+
Test.IsOk Value <= Max, Message
131+
End Sub
115132

116-
With Specs.It("should test complex things")
117-
.Expect(ThisWorkbook.Sheets("Hidden").Visible).ToNotEqual XlSheetVisibility.xlSheetVisible
118-
.Expect(ThisWorkbook.Sheets("Main").Cells(1, 1).Interior.Color).ToEqual RGB(255, 0, 0)
133+
With Suite.Test("...")
134+
ToBeWithin(.Self, Value, 0, 100)
119135
End With
120136
```
121137

122-
### ImmediateReporter
138+
__TestCase API__
139+
140+
- `Test.Name`
141+
- `Test.Self` - Reference to test case (useful inside of `With`)
142+
- `Test.Context` - `Dictionary` holding test context (useful for `BeforeEach`/`AfterEach`)
143+
- `Test.IsEqual(A, B, [Message])`
144+
- `Test.NotEqual(A, B, [Message])`
145+
- `Test.IsOk(Value, [Message])`
146+
- `Test.NotOk(Value, [Message])`
147+
- `Test.IsUndefined(Value, [Message])`
148+
- `Test.NotUndefined(Value, [Message])`
149+
- `Test.Includes(Values, Value, [Message])` - Check if value is included in array or `Collection`
150+
- `Test.NotIncludes(Values, Value, [Message])`
151+
- `Test.IsApproximate(A, B, SignificantFigures, [Message])` - Check if two values are close to each other (useful for `Double` values)
152+
- `Test.NotApproximate(A, B, SignificantFigures, [Message])`
153+
- `Test.Pass()` - Explicitly pass the test
154+
- `Test.Fail([Message])` - Explicitly fail the test
155+
- `Test.Plan(Count)` - For tests with loops and branches, it is important to catch if any assertions are skipped or extra
156+
- `Test.Skip()` - Notify suite to skip this test
157+
158+
Generally, more advanced assertions should be added with custom assertions functions (detailed above), but there are common assertions that will be added (e.g. `IsApproximate` = close within significant fixtures, `Includes` = array/collection includes value, )
123159

124-
With your specs 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.
160+
## ImmediateReporter
161+
162+
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.
125163

126164
```vb
127-
Public Function Specs As SpecSuite
128-
Set Specs = New SpecSuite
129-
Specs.Description = "..."
165+
Public Function Suite As TestSuite
166+
Set Suite = New TestSuite
167+
Suite.Description = "..."
130168

131-
' Create reporter and attach it to these specs
132-
Dim Reporter As New ImmediateReporter
133-
Reporter.ListenTo Specs
169+
' Create reporter and attach it to these specs
170+
Dim Reporter As New ImmediateReporter
171+
Reporter.ListenTo Suite
134172

135-
' -> Reporter will now output results as they are generated
173+
' -> Reporter will now output results as they are generated
136174
End Function
137175
```
138176

139-
### RunMatcher
177+
## Context / Lifecycle Hooks
140178

141-
For VBA applications that support `Application.Run` (which is at least Windows Excel, Word, and Access), you can create custom expect functions with `RunMatcher`.
179+
`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.
142180

143181
```vb
144-
Public Function Specs As SpecSuite
145-
Set Specs = New SpecSuite
146-
147-
With Specs.It("should be within 1 and 100")
148-
.Expect(50).RunMatcher "ToBeWithin", "to be within", 1, 100
149-
' ^ Actual
150-
' ^ Public Function to call
151-
' ^ message for matcher
152-
' ^ 0+ Args to pass to matcher
153-
End With
154-
End Function
182+
' Class TestFixture
183+
Private WithEvents pSuite As TestSuite
155184

156-
Public Function ToBeWithin(Actual As Variant, Args As Variant) As Variant
157-
If UBound(Args) - LBound(Args) < 1 Then
158-
' Return string for specific failure message
159-
ToBeWithin = "Need to pass in upper-bound to ToBeWithin"
160-
Else
161-
If Actual >= Args(0) And Actual <= Args(1) Then
162-
' Return true for pass
163-
ToBeWithin = True
164-
Else
165-
' Return false for fail or custom failure message
166-
ToBeWithin = False
167-
End If
168-
End If
169-
End Function
170-
```
185+
Public Sub ListenTo(Suite As TestSuite)
186+
Set pSuite = Suite
187+
End Sub
188+
189+
Private Sub pSuite_BeforeEach(Test As TestCase)
190+
Test.Context.Add "fixture", New Collection
191+
End Sub
192+
193+
Private Sub pSuite_AfterEach(Test As TestCase)
194+
' Context is cleared automatically,
195+
' but can manually cleanup here
196+
End Sub
171197

172-
To avoid compilation issues on unsupported applications, the compiler constant `EnableRunMatcher` in `SpecExpectation.cls` should be set to `False`.
198+
' Elsewhere
173199

174-
For more details, check out the [Wiki](https://github.com/VBA-tools/VBA-TDD/wiki)
200+
Dim Suite As New TestSuite
175201

176-
- Design based heavily on the [Jasmine](https://jasmine.github.io/)
177-
- Author: Tim Hall
178-
- License: MIT
202+
Dim Fixture As New TestFixture
203+
Fixture.ListenTo Suite
204+
205+
With Suite.Test("...")
206+
.Context("fixture").Add "..."
207+
End With
208+
```

specs/Specs_SpecDefinition.bas

Lines changed: 0 additions & 57 deletions
This file was deleted.

0 commit comments

Comments
 (0)