@@ -8,7 +8,7 @@ Attribute VB_Creatable = False
88Attribute VB_PredeclaredId = False
99Attribute VB_Exposed = True
1010''
11- ' SpecExpectation v1.2.2
11+ ' SpecExpectation v1.2.3
1212' (c) Tim Hall - https://github.com/timhall/Excel-TDD
1313'
1414' Provides various tests that can be performed for a provided value
@@ -40,27 +40,30 @@ Public FailureMessage As String
4040' --------------------------------------------- '
4141
4242Public Sub ToEqual (Value As Variant )
43- Dim failed As Boolean
44- failed = False
43+ Dim Failed As Boolean
44+ Failed = False
4545
4646 If IsError(Me.ExpectValue) Or IsError(Value) Then
47- failed = True
47+ Failed = True
4848
4949 ' If both the values are doubles, use decimal notequal comparison
5050 ElseIf VarType(Me.ExpectValue) = vbDouble And VarType(Value) = vbDouble Then
5151 If CDec(Me.ExpectValue) <> CDec(Value) Then
52- failed = True
52+ Failed = True
5353 End If
5454
5555 ' Otherwise use standard notequal comparison
56+ ElseIf VarType(Me.ExpectValue) = vbObject Or VarType(Value) = vbObject Then
57+ Fails "Unsupported: Can't compare objects"
58+ Exit Sub
5659 Else
5760 If Me.ExpectValue <> Value Then
58- failed = True
61+ Failed = True
5962 End If
6063 End If
6164
6265 ' If test fails, create failure message
63- If failed Then
66+ If Failed Then
6467 Fails CreateFailureMessage("to equal" , Value)
6568 Else
6669 Passes
@@ -74,10 +77,26 @@ End Sub
7477' --------------------------------------------- '
7578
7679Public Sub ToNotEqual (Value As Variant )
77- If Not IsError(Me.ExpectValue) And Not IsError(Value) And Me.ExpectValue <> Value Then
78- Passes
80+ Dim Failed As Boolean
81+ Failed = False
82+
83+ If Not IsError(Me.ExpectValue) And Not IsError(Value) Then
84+ If VarType(Me.ExpectValue) = vbObject Or VarType(Value) = vbObject Then
85+ Fails "Unsupported: Can't compare objects"
86+ Exit Sub
87+ ElseIf Me.ExpectValue <> Value Then
88+ Passes
89+ Else
90+ Failed = True
91+ End If
7992 Else
93+ Failed = True
94+ End If
95+
96+ If Failed Then
8097 Fails CreateFailureMessage("to not equal" , Value)
98+ Else
99+ Passes
81100 End If
82101End Sub
83102
@@ -87,17 +106,15 @@ End Sub
87106
88107Public Sub ToBeDefined ()
89108 ' Make sure the value isn't empty or null
90- ' (There may be other things that need to checked as well)
91- If Not IsEmpty(Me.ExpectValue) And Not IsNull(Me.ExpectValue) Then
109+ If VarType(Me.ExpectValue) = vbObject Then
110+ If Not Me.ExpectValue Is Nothing Then
111+ Passes
112+ Else
113+ Fails CreateFailureMessage("to be defined" )
114+ End If
115+ ElseIf Not IsEmpty(Me.ExpectValue) And Not IsNull(Me.ExpectValue) Then
92116 Passes
93117 Else
94- If VarType(Me.ExpectValue) = vbObject Then
95- If Not Me.ExpectValue Is Nothing Then
96- Passes
97- Exit Sub
98- End If
99- End If
100-
101118 Fails CreateFailureMessage("to be defined" )
102119 End If
103120End Sub
@@ -239,7 +256,16 @@ Private Sub Fails(Message As String)
239256End Sub
240257
241258Private Function GetStringForValue (Value As Variant ) As String
242- GetStringForValue = CStr(Value)
259+ If VarType(Value) = vbObject Then
260+ If Value Is Nothing Then
261+ GetStringForValue = "(Nothing)"
262+ Else
263+ GetStringForValue = "(Object)"
264+ End If
265+ Else
266+ GetStringForValue = CStr(Value)
267+ End If
268+
243269 If GetStringForValue = "" Then
244270 GetStringForValue = "(Undefined)"
245271 End If
0 commit comments