11Attribute 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
207230End Sub
208231
209232Private Sub ClearOutput ()
0 commit comments