Skip to content

Commit c993e1d

Browse files
committed
v2.0.0-beta.2
1 parent d24eaf4 commit c993e1d

6 files changed

+26
-23
lines changed

src/ImmediateReporter.cls

+1-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ Attribute VB_Creatable = False
88
Attribute VB_PredeclaredId = False
99
Attribute VB_Exposed = True
1010
''
11-
' ImmediateReporter v2.0.0-beta
11+
' ImmediateReporter v2.0.0-beta.2
1212
' (c) Tim Hall - https://github.com/VBA-tools/VBA-TDD
1313
'
1414
' Report results to Immediate Window

src/TestCase.cls

+1-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ Attribute VB_Creatable = False
88
Attribute VB_PredeclaredId = False
99
Attribute VB_Exposed = True
1010
''
11-
' TestCase v2.0.0-beta
11+
' TestCase v2.0.0-beta.2
1212
' (c) Tim Hall - https://github.com/vba-tools/vba-test
1313
'
1414
' Verify a single test case with assertions

src/TestSuite.cls

+1-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ Attribute VB_Creatable = False
88
Attribute VB_PredeclaredId = False
99
Attribute VB_Exposed = True
1010
''
11-
' TestSuite v2.0.0-beta
11+
' TestSuite v2.0.0-beta.2
1212
' (c) Tim Hall - https://github.com/vba-tools/vba-test
1313
'
1414
' A collection of tests, with events and results

src/WorkbookReporter.cls

+23-20
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ Attribute VB_Creatable = False
88
Attribute VB_PredeclaredId = False
99
Attribute VB_Exposed = True
1010
''
11-
' DisplayReporter v2.0.0-beta
11+
' DisplayReporter v2.0.0-beta.2
1212
' (c) Tim Hall - https://github.com/VBA-tools/VBA-TDD
1313
'
1414
' Report results to Worksheet
@@ -18,7 +18,7 @@ Attribute VB_Exposed = True
1818
' Platforms: Windows and Mac
1919
' Applications: Excel-only
2020
' @author tim.hall.engr@gmail.com
21-
' @license MIT (http://www.opensource.org/licenses/mit-license.php)
21+
' @license MIT (https://opensource.org/licenses/MIT)
2222
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
2323
Option Explicit
2424

@@ -72,9 +72,9 @@ End Sub
7272
' Output the given suite
7373
'
7474
' @method Output
75-
' @param {SpecSuite} Suite
75+
' @param {TestSuite} Suite
7676
''
77-
Public Sub Output(Suite As SpecSuite)
77+
Public Sub Output(Suite As TestSuite)
7878
pCount = pCount + 1
7979
pSuites.Add Suite
8080

@@ -89,9 +89,9 @@ End Sub
8989
''
9090
Public Sub Done()
9191
Dim Failed As Boolean
92-
Dim Suite As SpecSuite
92+
Dim Suite As TestSuite
9393
For Each Suite In pSuites
94-
If Suite.Result = SpecResultType.Fail Then
94+
If Suite.Result = TestResultType.Fail Then
9595
Failed = True
9696
Exit For
9797
End If
@@ -159,9 +159,10 @@ Private Sub DisplayResults()
159159
Dim Dividers As New Collection
160160
Dim Headings As New Collection
161161

162-
Dim Suite As SpecSuite
163-
Dim Spec As SpecDefinition
164-
Dim Expectation As SpecExpectation
162+
Dim Suite As TestSuite
163+
Dim Test As TestCase
164+
Dim Failure As Variant
165+
165166
For Each Suite In pSuites
166167
If Rows.Count > 0 Then
167168
Dividers.Add Rows.Count
@@ -172,13 +173,15 @@ Private Sub DisplayResults()
172173
Rows.Add Array(Suite.Description, ResultTypeToString(Suite.Result))
173174
End If
174175

175-
For Each Spec In Suite.Specs
176-
Rows.Add Array(Spec.Description, ResultTypeToString(Spec.Result))
177-
178-
For Each Expectation In Spec.FailedExpectations
179-
Rows.Add Array(" " & Expectation.FailureMessage, "")
180-
Next Expectation
181-
Next Spec
176+
For Each Test In Suite.Tests
177+
If Test.Result <> TestResultType.Skipped Then
178+
Rows.Add Array(Test.Name, ResultTypeToString(Test.Result))
179+
180+
For Each Failure In Test.Failures
181+
Rows.Add Array(" " & Failure, "")
182+
Next Failure
183+
End If
184+
Next Test
182185
Next Suite
183186

184187
Dim OutputValues() As String
@@ -214,13 +217,13 @@ Private Sub DisplayResults()
214217
Next Heading
215218
End Sub
216219

217-
Private Function ResultTypeToString(ResultType As SpecResultType) As String
220+
Private Function ResultTypeToString(ResultType As TestResultType) As String
218221
Select Case ResultType
219-
Case SpecResultType.Pass
222+
Case TestResultType.Pass
220223
ResultTypeToString = "Pass"
221-
Case SpecResultType.Fail
224+
Case TestResultType.Fail
222225
ResultTypeToString = "Fail"
223-
Case SpecResultType.Pending
226+
Case TestResultType.Pending
224227
ResultTypeToString = "Pending"
225228
End Select
226229
End Function

tests/vba-test-tests.xlsm

48 Bytes
Binary file not shown.

vba-test-blank.xlsm

26.1 KB
Binary file not shown.

0 commit comments

Comments
 (0)