Skip to content

Commit

Permalink
Merge pull request #27 from VBA-tools/group
Browse files Browse the repository at this point in the history
Add Suite Grouping
  • Loading branch information
timhall committed Sep 2, 2019
2 parents e7af4a0 + 69460d4 commit 56a1334
Show file tree
Hide file tree
Showing 11 changed files with 100 additions and 245 deletions.
2 changes: 2 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
build

# Ignore temporary Office files and OS files
*/~$*
.DS_Store
2 changes: 1 addition & 1 deletion src/ImmediateReporter.cls
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ Private Sub pSuite_Result(Test As TestCase)
Exit Sub
End If

Debug.Print ResultTypeToString(Test.Result) & " " & Test.Name
Debug.Print ResultTypeToString(Test.Result) & " " & Test.Description

If Test.Result = TestResultType.Fail Then
Dim Failure As Variant
Expand Down
2 changes: 1 addition & 1 deletion src/TestCase.cls
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ Private pFailures As VBA.Collection
' Events and Properties
' --------------------------------------------- '

Public Name As String
Public Description As String
Public Context As Dictionary

Public Planned As Long
Expand Down
67 changes: 62 additions & 5 deletions src/TestSuite.cls
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ End Enum
Public Event BeforeEach(Test As TestCase)
Public Event Result(Test As TestCase)
Public Event AfterEach(Test As TestCase)
Public Event Group(Suite As TestSuite)

''
' (Optional) description of suite for display in runners
Expand All @@ -48,6 +49,11 @@ Public Description As String
''
Public Tests As VBA.Collection

''
' @internal
''
Public Parent As TestSuite

''
' Compute suite result from tests
'
Expand Down Expand Up @@ -100,33 +106,84 @@ Public Property Get SkippedTests() As VBA.Collection
Set SkippedTests = GetTestsByType(TestResultType.Skipped)
End Property

Public Property Get Self() As TestSuite
Set Self = Me
End Property

' ============================================= '
' Public Methods
' ============================================= '

''
' Create a new test case with name
' Create a new test case with description
'
' @method Test
' @param {String} Name
' @param {String} Description
' @returns {TestCase}
''
Public Function Test(Name As String) As TestCase
Public Function Test(Description As String) As TestCase
Dim Instance As New TestCase

Instance.Name = Name
Instance.Description = Description
Set Instance.Suite = Me

RaiseEvent BeforeEach(Instance)
OnTestBefore Instance

Set Test = Instance
End Function

Public Function Group(Description As String) As TestSuite
Dim Instance As New TestSuite

Instance.Description = Description
Set Instance.Parent = Me

RaiseEvent Group(Instance)

Set Group = Instance
End Function

''
' @internal
''
Public Sub TestComplete(Test As TestCase)
Tests.Add Test

OnTestResult Test
OnTestAfter Test
End Sub

''
' @internal
''
Public Sub OnTestBefore(Test As TestCase)
If Not Me.Parent Is Nothing Then
Me.Parent.OnTestBefore Test
End If

RaiseEvent BeforeEach(Test)
End Sub

''
' @internal
''
Public Sub OnTestResult(Test As TestCase)
RaiseEvent Result(Test)

If Not Me.Parent Is Nothing Then
Me.Parent.OnTestResult Test
End If
End Sub

''
' @internal
''
Public Sub OnTestAfter(Test As TestCase)
RaiseEvent AfterEach(Test)

If Not Me.Parent Is Nothing Then
Me.Parent.OnTestAfter Test
End If
End Sub

' ============================================= '
Expand Down
233 changes: 0 additions & 233 deletions src/WorkbookReporter.cls

This file was deleted.

5 changes: 5 additions & 0 deletions tests/Tests.bas
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
Attribute VB_Name = "Tests"
Public Sub RunTests()
Tests_TestSuite.Tests
Tests_TestCase.Tests
End Sub
10 changes: 5 additions & 5 deletions tests/Tests_TestSuite.bas
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ Public Function Tests() As TestSuite
End With

With Tests.Test("should fire Result event")
.IsEqual Fixture.ResultCalls(1).Name, "should fire BeforeEach event"
.IsEqual Fixture.ResultCalls(1).Description, "should fire BeforeEach event"
.IsEqual Fixture.ResultCalls(1).Result, TestResultType.Pass
End With

Expand Down Expand Up @@ -44,10 +44,10 @@ Public Function Tests() As TestSuite
.IsEqual Suite.PendingTests.Count, 1
.IsEqual Suite.SkippedTests.Count, 1

.IsEqual Suite.PassedTests(1).Name, "(pass)"
.IsEqual Suite.FailedTests(1).Name, "(fail)"
.IsEqual Suite.PendingTests(1).Name, "(pending)"
.IsEqual Suite.SkippedTests(1).Name, "(skipped)"
.IsEqual Suite.PassedTests(1).Description, "(pass)"
.IsEqual Suite.FailedTests(1).Description, "(fail)"
.IsEqual Suite.PendingTests(1).Description, "(pending)"
.IsEqual Suite.SkippedTests(1).Description, "(skipped)"
End With

With Tests.Test("should have overall result")
Expand Down
Binary file removed tests/vba-test-tests.xlsm
Binary file not shown.
Loading

0 comments on commit 56a1334

Please sign in to comment.