Skip to content

Commit 091e4c5

Browse files
committed
v1.2.2 Small changes
- DisplayRunner shows SpecSuite details - Add `ToContain` and `ToNotContain` expectations
1 parent 4fa518b commit 091e4c5

File tree

11 files changed

+72
-17
lines changed

11 files changed

+72
-17
lines changed

src/BlankIWBProxy.cls

Lines changed: 1 addition & 1 deletion
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 = False
1010
''
11-
' BlankIWBProxy v1.2.1
11+
' BlankIWBProxy v1.2.2
1212
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313
'
1414
' Blank implementation of IWBProxy

src/DisplayRunner.bas

Lines changed: 30 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
Attribute VB_Name = "DisplayRunner"
22
''
3-
' DisplayRunner v1.2.1
3+
' DisplayRunner v1.2.2
44
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
55
'
66
' Runner with sheet output
@@ -137,6 +137,7 @@ Public Sub RunSuites(SuiteCol As Collection, Optional Append As Boolean = False)
137137
Dim Suite As SpecSuite
138138
Dim Spec As SpecDefinition
139139
Dim Row As Integer
140+
Dim Indentation As String
140141

141142
' 0. Disable screen updating
142143
Dim PrevUpdating As Boolean
@@ -153,8 +154,15 @@ Public Sub RunSuites(SuiteCol As Collection, Optional Append As Boolean = False)
153154
Row = NewOutputRow
154155
For Each Suite In SuiteCol
155156
If Not Suite Is Nothing Then
157+
If Suite.Description <> "" Then
158+
OutputSuiteDetails Suite, Row
159+
Indentation = " "
160+
Else
161+
Indentation = ""
162+
End If
163+
156164
For Each Spec In Suite.SpecsCol
157-
OutputSpec Spec, Row
165+
OutputSpec Spec, Row, Indentation
158166
Next Spec
159167
End If
160168
Next Suite
@@ -189,21 +197,36 @@ End Sub
189197
' Internal
190198
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
191199

192-
Private Sub OutputSpec(Spec As SpecDefinition, ByRef Row As Integer)
193-
200+
Private Sub OutputSpec(Spec As SpecDefinition, ByRef Row As Integer, Optional Indentation As String = "")
194201
Sheet.Cells(Row, IdCol) = Spec.Id
195-
Sheet.Cells(Row, DescCol) = "It " & Spec.Description
202+
Sheet.Cells(Row, DescCol) = Indentation & Spec.Description
196203
Sheet.Cells(Row, ResultCol) = Spec.ResultName
197204
Row = Row + 1
198205

199-
If Spec.FailedExpectations.Count > 0 Then
206+
If Spec.FailedExpectations.count > 0 Then
200207
Dim Exp As SpecExpectation
201208
For Each Exp In Spec.FailedExpectations
202-
Sheet.Cells(Row, DescCol) = "X " & Exp.FailureMessage
209+
Sheet.Cells(Row, DescCol) = Indentation & "X " & Exp.FailureMessage
203210
Row = Row + 1
204211
Next Exp
205212
End If
213+
End Sub
214+
215+
Private Sub OutputSuiteDetails(Suite As SpecSuite, ByRef Row As Integer)
216+
Dim HasFailure As Boolean
217+
Dim Result As String
218+
Result = "Pass"
206219

220+
For Each Spec In Suite.SpecsCol
221+
If Spec.Result = SpecResult.Fail Then
222+
Result = "Fail"
223+
Exit For
224+
End If
225+
Next Spec
226+
227+
Sheet.Cells(Row, DescCol) = Suite.Description
228+
Sheet.Cells(Row, ResultCol) = Result
229+
Row = Row + 1
207230
End Sub
208231

209232
Private Sub ClearOutput()

src/IScenario.cls

Lines changed: 1 addition & 1 deletion
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-
' IScenario v1.2.1
11+
' IScenario v1.2.2
1212
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313
'
1414
' Interface for creating and running scenarios on workbooks

src/IWBProxy.cls

Lines changed: 1 addition & 1 deletion
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-
' IWBProxy v1.2.1
11+
' IWBProxy v1.2.2
1212
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313
'
1414
' Interface for generic workbook proxies

src/InlineRunner.bas

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
Attribute VB_Name = "InlineRunner"
22
''
3-
' InlineRunner v1.2.1
3+
' InlineRunner v1.2.2
44
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
55
'
66
' Runner for outputting results of specs to Immediate window

src/Scenario.cls

Lines changed: 1 addition & 1 deletion
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-
' Scenario v1.2.1
11+
' Scenario v1.2.2
1212
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313
'
1414
' Generic implementation of scenario

src/SpecDefinition.cls

Lines changed: 1 addition & 1 deletion
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-
' SpecDefinition v1.2.1
11+
' SpecDefinition v1.2.2
1212
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313
'
1414
' Provides helpers and acts as workbook proxy

src/SpecExpectation.cls

Lines changed: 33 additions & 1 deletion
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-
' SpecExpectation v1.2.1
11+
' SpecExpectation v1.2.2
1212
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313
'
1414
' Provides various tests that can be performed for a provided value
@@ -190,6 +190,38 @@ Public Sub ToBeGTE(Value As Variant)
190190
Call ToBeGreaterThanOrEqualTo(Value)
191191
End Sub
192192

193+
''
194+
' Check if the defined string contains the test string
195+
'
196+
' @param {Variant} Value
197+
' --------------------------------------------- '
198+
199+
Public Sub ToContain(Value As Variant, Optional MatchCase As Boolean = True)
200+
If MatchCase And InStr(Me.ExpectValue, Value) > 0 Then
201+
Passes
202+
ElseIf Not MatchCase And InStr(UCase(Me.ExpectValue), UCase(Value)) > 0 Then
203+
Passes
204+
Else
205+
Fails CreateFailureMessage("to contain", Value)
206+
End If
207+
End Sub
208+
209+
''
210+
' Check that the defined string does not contain the test string
211+
'
212+
' @param {Variant} Value
213+
' --------------------------------------------- '
214+
215+
Public Sub ToNotContain(Value As Variant, Optional MatchCase As Boolean = True)
216+
If MatchCase And InStr(Me.ExpectValue, Value) > 0 Then
217+
Fails CreateFailureMessage("to not contain", Value)
218+
ElseIf Not MatchCase And InStr(UCase(Me.ExpectValue), UCase(Value)) > 0 Then
219+
Fails CreateFailureMessage("to not contain", Value)
220+
Else
221+
Passes
222+
End If
223+
End Sub
224+
193225

194226
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
195227
' Internal Methods

src/SpecHelpers.bas

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
Attribute VB_Name = "SpecHelpers"
22
''
3-
' SpecHelpers v1.2.1
3+
' SpecHelpers v1.2.2
44
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
55
'
66
' General utilities for specs

src/SpecSuite.cls

Lines changed: 1 addition & 1 deletion
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-
' SpecSuite v1.2.1
11+
' SpecSuite v1.2.2
1212
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313
'
1414
' A collection of specs with the workbook that they act on

0 commit comments

Comments
 (0)