Skip to content

Commit d1b36e6

Browse files
committed
Merge pull request #5 from timhall/double-comparison
Update ToEqual and ToBeCloseTo
2 parents 88f981b + 5198867 commit d1b36e6

File tree

6 files changed

+59
-38
lines changed

6 files changed

+59
-38
lines changed

.DS_Store

6 KB
Binary file not shown.

.gitattributes

Lines changed: 8 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,22 +1,16 @@
1-
# Auto detect text files and perform LF normalization
1+
# CRLF -> LF by default, but not for modules or classes (especially classes)
22
* text=auto
3-
4-
# Custom for Visual Studio
5-
*.cs diff=csharp
6-
*.sln merge=union
7-
*.csproj merge=union
8-
*.vbproj merge=union
9-
*.fsproj merge=union
10-
*.dbproj merge=union
3+
*.bas text eol=crlf
4+
*.cls text eol=crlf
115

126
# Standard to msysgit
13-
*.doc diff=astextplain
14-
*.DOC diff=astextplain
7+
*.doc diff=astextplain
8+
*.DOC diff=astextplain
159
*.docx diff=astextplain
1610
*.DOCX diff=astextplain
1711
*.dot diff=astextplain
1812
*.DOT diff=astextplain
1913
*.pdf diff=astextplain
20-
*.PDF diff=astextplain
21-
*.rtf diff=astextplain
22-
*.RTF diff=astextplain
14+
*.PDF diff=astextplain
15+
*.rtf diff=astextplain
16+
*.RTF diff=astextplain

.gitignore

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
# Ignore temporary Excel files
22
*/~$*
33

4-
# Ignore scratch work
5-
_scratch
4+
# Ignore scratch work and other files
5+
_scratch
6+
.DS_Store

specs/Excel-TDD - Specs.xlsm

4.85 KB
Binary file not shown.

specs/SpecExpectationSpecs.bas

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,19 @@ Public Function Specs() As SpecSuite
1717
.Expect(False).ToNotEqual True
1818
End With
1919

20+
With Specs.It("ToEqual/ToNotEqual with Double")
21+
' Compare to 15 significant figures
22+
.Expect(123456789012345#).ToEqual 123456789012345#
23+
.Expect(1.50000000000001).ToEqual 1.50000000000001
24+
.Expect(Val("1234567890123450")).ToEqual Val("1234567890123451")
25+
.Expect(Val("0.1000000000000010")).ToEqual Val("0.1000000000000011")
26+
27+
.Expect(123456789012344#).ToNotEqual 123456789012345#
28+
.Expect(1.5).ToNotEqual 1.50000000000001
29+
.Expect(Val("1234567890123454")).ToNotEqual Val("1234567890123456")
30+
.Expect(Val("0.1000000000000014")).ToNotEqual Val("0.1000000000000016")
31+
End With
32+
2033
With Specs.It("ToBeUndefined/ToNotBeUndefined")
2134
.Expect(Nothing).ToBeUndefined
2235
.Expect(Empty).ToBeUndefined
@@ -118,9 +131,9 @@ Public Function Specs() As SpecSuite
118131
End With
119132

120133
With Specs.It("ToBeCloseTo")
121-
.Expect(3.1415926).ToNotBeCloseTo 2.78, 2
134+
.Expect(3.1415926).ToNotBeCloseTo 2.78, 3
122135

123-
.Expect(3.1415926).ToBeCloseTo 2.78, 0
136+
.Expect(3.1415926).ToBeCloseTo 2.78, 1
124137
End With
125138

126139
With Specs.It("ToContain")

src/SpecExpectation.cls

Lines changed: 33 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -52,15 +52,12 @@ Private Function IsEqual(Actual As Variant, Expected As Variant) As Variant
5252
ElseIf IsObject(Actual) Or IsObject(Expected) Then
5353
IsEqual = "Unsupported: Can't compare objects"
5454
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
5656
' 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)
6461
Else
6562
IsEqual = Actual = Expected
6663
End If
@@ -221,20 +218,36 @@ End Function
221218
' Check if the actual value is close to the expected value
222219
'
223220
' @param {Variant} Expected
224-
' @param {Integer} DecimalPlaces
221+
' @param {Integer} SignificantFigures (1-15)
225222
' --------------------------------------------- '
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
228225
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
231228
End Sub
232229

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
238251
End If
239252
End Function
240253

@@ -251,7 +264,7 @@ Public Sub ToContain(Expected As Variant, Optional MatchCase As Boolean = True)
251264
If MatchCase Then
252265
Check Matches(Me.Actual, Expected), "to match", Expected:=Expected
253266
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
255268
End If
256269
Else
257270
Check Contains(Me.Actual, Expected), "to contain", Expected:=Expected
@@ -263,7 +276,7 @@ Public Sub ToNotContain(Expected As Variant, Optional MatchCase As Boolean = Tru
263276
If MatchCase Then
264277
Check Matches(Me.Actual, Expected), "to not match", Expected:=Expected, Inverse:=True
265278
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
267280
End If
268281
Else
269282
Check Contains(Me.Actual, Expected), "to not contain", Expected:=Expected, Inverse:=True

0 commit comments

Comments
 (0)