Skip to content

Commit

Permalink
v1.2.2 Small changes
Browse files Browse the repository at this point in the history
- DisplayRunner shows SpecSuite details
- Add `ToContain` and `ToNotContain` expectations
  • Loading branch information
timhall committed Oct 23, 2013
1 parent 4fa518b commit 091e4c5
Show file tree
Hide file tree
Showing 11 changed files with 72 additions and 17 deletions.
2 changes: 1 addition & 1 deletion src/BlankIWBProxy.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
''
' BlankIWBProxy v1.2.1
' BlankIWBProxy v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Blank implementation of IWBProxy
Expand Down
37 changes: 30 additions & 7 deletions src/DisplayRunner.bas
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Attribute VB_Name = "DisplayRunner"
''
' DisplayRunner v1.2.1
' DisplayRunner v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Runner with sheet output
Expand Down Expand Up @@ -137,6 +137,7 @@ Public Sub RunSuites(SuiteCol As Collection, Optional Append As Boolean = False)
Dim Suite As SpecSuite
Dim Spec As SpecDefinition
Dim Row As Integer
Dim Indentation As String

' 0. Disable screen updating
Dim PrevUpdating As Boolean
Expand All @@ -153,8 +154,15 @@ Public Sub RunSuites(SuiteCol As Collection, Optional Append As Boolean = False)
Row = NewOutputRow
For Each Suite In SuiteCol
If Not Suite Is Nothing Then
If Suite.Description <> "" Then
OutputSuiteDetails Suite, Row
Indentation = " "
Else
Indentation = ""
End If

For Each Spec In Suite.SpecsCol
OutputSpec Spec, Row
OutputSpec Spec, Row, Indentation
Next Spec
End If
Next Suite
Expand Down Expand Up @@ -189,21 +197,36 @@ End Sub
' Internal
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '

Private Sub OutputSpec(Spec As SpecDefinition, ByRef Row As Integer)

Private Sub OutputSpec(Spec As SpecDefinition, ByRef Row As Integer, Optional Indentation As String = "")
Sheet.Cells(Row, IdCol) = Spec.Id
Sheet.Cells(Row, DescCol) = "It " & Spec.Description
Sheet.Cells(Row, DescCol) = Indentation & Spec.Description
Sheet.Cells(Row, ResultCol) = Spec.ResultName
Row = Row + 1

If Spec.FailedExpectations.Count > 0 Then
If Spec.FailedExpectations.count > 0 Then
Dim Exp As SpecExpectation
For Each Exp In Spec.FailedExpectations
Sheet.Cells(Row, DescCol) = "X " & Exp.FailureMessage
Sheet.Cells(Row, DescCol) = Indentation & "X " & Exp.FailureMessage
Row = Row + 1
Next Exp
End If
End Sub

Private Sub OutputSuiteDetails(Suite As SpecSuite, ByRef Row As Integer)
Dim HasFailure As Boolean
Dim Result As String
Result = "Pass"

For Each Spec In Suite.SpecsCol
If Spec.Result = SpecResult.Fail Then
Result = "Fail"
Exit For
End If
Next Spec

Sheet.Cells(Row, DescCol) = Suite.Description
Sheet.Cells(Row, ResultCol) = Result
Row = Row + 1
End Sub

Private Sub ClearOutput()
Expand Down
2 changes: 1 addition & 1 deletion src/IScenario.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' IScenario v1.2.1
' IScenario v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Interface for creating and running scenarios on workbooks
Expand Down
2 changes: 1 addition & 1 deletion src/IWBProxy.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' IWBProxy v1.2.1
' IWBProxy v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Interface for generic workbook proxies
Expand Down
2 changes: 1 addition & 1 deletion src/InlineRunner.bas
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Attribute VB_Name = "InlineRunner"
''
' InlineRunner v1.2.1
' InlineRunner v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Runner for outputting results of specs to Immediate window
Expand Down
2 changes: 1 addition & 1 deletion src/Scenario.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' Scenario v1.2.1
' Scenario v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Generic implementation of scenario
Expand Down
2 changes: 1 addition & 1 deletion src/SpecDefinition.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' SpecDefinition v1.2.1
' SpecDefinition v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Provides helpers and acts as workbook proxy
Expand Down
34 changes: 33 additions & 1 deletion src/SpecExpectation.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' SpecExpectation v1.2.1
' SpecExpectation v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Provides various tests that can be performed for a provided value
Expand Down Expand Up @@ -190,6 +190,38 @@ Public Sub ToBeGTE(Value As Variant)
Call ToBeGreaterThanOrEqualTo(Value)
End Sub

''
' Check if the defined string contains the test string
'
' @param {Variant} Value
' --------------------------------------------- '

Public Sub ToContain(Value As Variant, Optional MatchCase As Boolean = True)
If MatchCase And InStr(Me.ExpectValue, Value) > 0 Then
Passes
ElseIf Not MatchCase And InStr(UCase(Me.ExpectValue), UCase(Value)) > 0 Then
Passes
Else
Fails CreateFailureMessage("to contain", Value)
End If
End Sub

''
' Check that the defined string does not contain the test string
'
' @param {Variant} Value
' --------------------------------------------- '

Public Sub ToNotContain(Value As Variant, Optional MatchCase As Boolean = True)
If MatchCase And InStr(Me.ExpectValue, Value) > 0 Then
Fails CreateFailureMessage("to not contain", Value)
ElseIf Not MatchCase And InStr(UCase(Me.ExpectValue), UCase(Value)) > 0 Then
Fails CreateFailureMessage("to not contain", Value)
Else
Passes
End If
End Sub


' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
' Internal Methods
Expand Down
2 changes: 1 addition & 1 deletion src/SpecHelpers.bas
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Attribute VB_Name = "SpecHelpers"
''
' SpecHelpers v1.2.1
' SpecHelpers v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' General utilities for specs
Expand Down
2 changes: 1 addition & 1 deletion src/SpecSuite.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' SpecSuite v1.2.1
' SpecSuite v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' A collection of specs with the workbook that they act on
Expand Down
2 changes: 1 addition & 1 deletion src/WBProxy.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' WBProxy v1.2.1
' WBProxy v1.2.2
' (c) Tim Hall - https://github.com/timhall/Excel-TDD
'
' Generic implementation of workbook proxy
Expand Down

0 comments on commit 091e4c5

Please sign in to comment.