@@ -52,15 +52,12 @@ Private Function IsEqual(Actual As Variant, Expected As Variant) As Variant
52
52
ElseIf IsObject(Actual) Or IsObject(Expected) Then
53
53
IsEqual = "Unsupported: Can't compare objects"
54
54
ElseIf VarType(Actual) = vbDouble And VarType(Expected) = vbDouble Then
55
- ' It is inherently difficult to check equality of Double
55
+ ' It is inherently difficult/almost impossible to check equality of Double
56
56
' http://support.microsoft.com/kb/78113
57
- ' Windows: compare with CDec
58
- ' Mac: (CDec not available) compare to 22 decimal places
59
- #If Mac Then
60
- IsEqual = Round(Actual - Expected, 22 ) = 0 #
61
- #Else
62
- IsEqual = CDec(Actual) = CDec(Expected)
63
- #End If
57
+ '
58
+ ' Compare up to 15 significant figures
59
+ ' -> Format as scientific notation with 15 significant figures and then compare strings
60
+ IsEqual = IsCloseTo(Actual, Expected, 15 )
64
61
Else
65
62
IsEqual = Actual = Expected
66
63
End If
@@ -221,20 +218,36 @@ End Function
221
218
' Check if the actual value is close to the expected value
222
219
'
223
220
' @param {Variant} Expected
224
- ' @param {Integer} DecimalPlaces
221
+ ' @param {Integer} SignificantFigures (1-15)
225
222
' --------------------------------------------- '
226
- Public Sub ToBeCloseTo (Expected As Variant , DecimalPlaces As Integer )
227
- Check IsCloseTo(Me.Actual, Expected, DecimalPlaces ), "to be close to" , Expected:=Expected
223
+ Public Sub ToBeCloseTo (Expected As Variant , SignificantFigures As Integer )
224
+ Check IsCloseTo(Me.Actual, Expected, SignificantFigures ), "to be close to" , Expected:=Expected
228
225
End Sub
229
- Public Sub ToNotBeCloseTo (Expected As Variant , DecimalPlaces As Integer )
230
- Check IsCloseTo(Me.Actual, Expected, DecimalPlaces ), "to be close to" , Expected:=Expected, Inverse:=True
226
+ Public Sub ToNotBeCloseTo (Expected As Variant , SignificantFigures As Integer )
227
+ Check IsCloseTo(Me.Actual, Expected, SignificantFigures ), "to be close to" , Expected:=Expected, Inverse:=True
231
228
End Sub
232
229
233
- Private Function IsCloseTo (Actual As Variant , Expected As Variant , DecimalPlaces As Integer ) As Variant
234
- If IsError(Actual) Or IsError(Expected) Or Round(Actual, DecimalPlaces) <> Round(Expected, DecimalPlaces) Then
235
- IsCloseTo = False
236
- Else
237
- IsCloseTo = True
230
+ Private Function IsCloseTo (Actual As Variant , Expected As Variant , SignificantFigures As Integer ) As Variant
231
+ Dim ActualAsString As String
232
+ Dim ExpectedAsString As String
233
+
234
+ If SignificantFigures < 1 Or SignificantFigures > 15 Then
235
+ IsCloseTo = "ToBeCloseTo/ToNotBeClose to can only compare from 1 to 15 significant figures"""
236
+ ElseIf Not IsError(Actual) And Not IsError(Expected) Then
237
+ ' Convert values to scientific notation strings and then compare strings
238
+ If Actual > 1 Then
239
+ ActualAsString = VBA.Format$(Actual, VBA.Left$("0.00000000000000" , SignificantFigures + 1 ) & "e+0" )
240
+ Else
241
+ ActualAsString = VBA.Format$(Actual, VBA.Left$("0.00000000000000" , SignificantFigures + 1 ) & "e-0" )
242
+ End If
243
+
244
+ If Expected > 1 Then
245
+ ExpectedAsString = VBA.Format$(Expected, VBA.Left$("0.00000000000000" , SignificantFigures + 1 ) & "e+0" )
246
+ Else
247
+ ExpectedAsString = VBA.Format$(Expected, VBA.Left$("0.00000000000000" , SignificantFigures + 1 ) & "e-0" )
248
+ End If
249
+
250
+ IsCloseTo = ActualAsString = ExpectedAsString
238
251
End If
239
252
End Function
240
253
@@ -251,7 +264,7 @@ Public Sub ToContain(Expected As Variant, Optional MatchCase As Boolean = True)
251
264
If MatchCase Then
252
265
Check Matches(Me.Actual, Expected), "to match" , Expected:=Expected
253
266
Else
254
- Check Matches(UCase(Me.Actual), UCase(Expected)), "to match" , Expected:=Expected
267
+ Check Matches(VBA. UCase$ (Me.Actual), VBA. UCase$ (Expected)), "to match" , Expected:=Expected
255
268
End If
256
269
Else
257
270
Check Contains(Me.Actual, Expected), "to contain" , Expected:=Expected
@@ -263,7 +276,7 @@ Public Sub ToNotContain(Expected As Variant, Optional MatchCase As Boolean = Tru
263
276
If MatchCase Then
264
277
Check Matches(Me.Actual, Expected), "to not match" , Expected:=Expected, Inverse:=True
265
278
Else
266
- Check Matches(UCase(Me.Actual), UCase(Expected)), "to not match" , Expected:=Expected, Inverse:=True
279
+ Check Matches(VBA. UCase$ (Me.Actual), VBA. UCase$ (Expected)), "to not match" , Expected:=Expected, Inverse:=True
267
280
End If
268
281
Else
269
282
Check Contains(Me.Actual, Expected), "to not contain" , Expected:=Expected, Inverse:=True
0 commit comments