Skip to content

Commit 9a675e0

Browse files
committed
Create TestRunner.bas
1 parent b1628d4 commit 9a675e0

File tree

1 file changed

+254
-0
lines changed

1 file changed

+254
-0
lines changed

src/Tests/TestRunner.bas

Lines changed: 254 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,254 @@
1+
Attribute VB_Name = "TestRunner"
2+
Option Explicit
3+
Option Private Module
4+
Private Evaluator As VBAexpressions
5+
Private expected As String
6+
Private actual As String
7+
8+
'@TestModule
9+
'@Folder("Tests")
10+
11+
Private Assert As Object
12+
Private Fakes As Object
13+
14+
'@ModuleInitialize
15+
Private Sub ModuleInitialize()
16+
'this method runs once per module.
17+
Set Assert = CreateObject("Rubberduck.AssertClass")
18+
Set Fakes = CreateObject("Rubberduck.FakesProvider")
19+
End Sub
20+
21+
'@ModuleCleanup
22+
Private Sub ModuleCleanup()
23+
'this method runs once per module.
24+
Set Assert = Nothing
25+
Set Fakes = Nothing
26+
End Sub
27+
28+
'@TestInitialize
29+
Private Sub TestInitialize()
30+
'This method runs before every test in the module..
31+
End Sub
32+
33+
'@TestCleanup
34+
Private Sub TestCleanup()
35+
'this method runs after every test in the module.
36+
End Sub
37+
38+
Private Function GetResult(Expression As String _
39+
, Optional VariablesValues As String = vbNullString) As String
40+
On Error Resume Next
41+
Set Evaluator = New VBAexpressions
42+
43+
With Evaluator
44+
.Create Expression
45+
GetResult = .Eval(VariablesValues)
46+
End With
47+
End Function
48+
49+
'@TestMethod("VBA Expressions")
50+
Private Sub Parentheses()
51+
On Error GoTo TestFail
52+
53+
actual = GetResult( _
54+
"(((((((((((-123.456-654.321)*1.1)*2.2)*3.3)+4.4)+5.5)+6.6)*7.7)*8.8)+9.9)+10.10)" _
55+
)
56+
expected = "-419741.48578672"
57+
Assert.AreEqual actual, expected
58+
59+
TestExit:
60+
Exit Sub
61+
TestFail:
62+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
63+
Resume TestExit
64+
End Sub
65+
'@TestMethod("VBA Expressions")
66+
Private Sub ParenthesesAndSingleFunction()
67+
On Error GoTo TestFail
68+
69+
actual = GetResult( _
70+
"(1+(2-5)*3+8/(5+3)^2)/sqr(4^2+3^2)" _
71+
)
72+
expected = "-1.575"
73+
Assert.AreEqual actual, expected
74+
75+
TestExit:
76+
Exit Sub
77+
TestFail:
78+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
79+
Resume TestExit
80+
End Sub
81+
'@TestMethod("VBA Expressions")
82+
Private Sub FunctionsWithMoreThanOneArgument()
83+
On Error GoTo TestFail
84+
85+
actual = GetResult( _
86+
"min(5;6;max(-0.6;-3))" _
87+
)
88+
expected = "-0.6"
89+
Assert.AreEqual actual, expected
90+
91+
TestExit:
92+
Exit Sub
93+
TestFail:
94+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
95+
Resume TestExit
96+
End Sub
97+
'@TestMethod("VBA Expressions")
98+
Private Sub NestedFunctions()
99+
On Error GoTo TestFail
100+
101+
actual = GetResult( _
102+
"tan(sqr(abs(ln(x))))" _
103+
, "x = " & Exp(1) _
104+
)
105+
expected = "1.5574077246549"
106+
Assert.AreEqual actual, expected
107+
108+
TestExit:
109+
Exit Sub
110+
TestFail:
111+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
112+
Resume TestExit
113+
End Sub
114+
'@TestMethod("VBA Expressions")
115+
Private Sub FloatingPointArithmetic()
116+
On Error GoTo TestFail
117+
118+
actual = GetResult( _
119+
"(1.434E3+1000)*2/3.235E-5" _
120+
)
121+
expected = "150479134.46677"
122+
Assert.AreEqual actual, expected
123+
124+
TestExit:
125+
Exit Sub
126+
TestFail:
127+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
128+
Resume TestExit
129+
End Sub
130+
'@TestMethod("VBA Expressions")
131+
Private Sub ExponentiationPrecedence()
132+
On Error GoTo TestFail
133+
134+
actual = GetResult( _
135+
"4^3^2" _
136+
)
137+
expected = "262144"
138+
Assert.AreEqual actual, expected
139+
140+
TestExit:
141+
Exit Sub
142+
TestFail:
143+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
144+
Resume TestExit
145+
End Sub
146+
'@TestMethod("VBA Expressions")
147+
Private Sub Factorials()
148+
On Error GoTo TestFail
149+
150+
actual = GetResult( _
151+
"25!/(24!)" _
152+
)
153+
expected = "25"
154+
Assert.AreEqual actual, expected
155+
156+
TestExit:
157+
Exit Sub
158+
TestFail:
159+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
160+
Resume TestExit
161+
End Sub
162+
'@TestMethod("VBA Expressions")
163+
Private Sub Precedence()
164+
On Error GoTo TestFail
165+
166+
actual = GetResult( _
167+
"5avg(2;abs(-3-7tan(5));9)-12pi-e+(7/sin(30)-4!)*min(cos(30);cos(150))" _
168+
)
169+
expected = "7.56040693890688"
170+
Assert.AreEqual actual, expected
171+
172+
TestExit:
173+
Exit Sub
174+
TestFail:
175+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
176+
Resume TestExit
177+
End Sub
178+
'@TestMethod("VBA Expressions")
179+
Private Sub Variables()
180+
On Error GoTo TestFail
181+
182+
actual = GetResult( _
183+
"Pi.e * 5.2Pie.1 + 3.1Pie" _
184+
, "Pi.e = 1; Pie.1 = 2; Pie = 3" _
185+
)
186+
expected = "19.7"
187+
Assert.AreEqual actual, expected
188+
189+
TestExit:
190+
Exit Sub
191+
TestFail:
192+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
193+
Resume TestExit
194+
End Sub
195+
'@TestMethod("VBA Expressions")
196+
Private Sub UDFsAndArrays()
197+
On Error GoTo TestFail
198+
'///////////////////////////////////////////////////////////////////////////////////
199+
' For illustrative purposes only. These UDFs are already implemented.
200+
'
201+
' Dim UDFnames() As Variant
202+
' UDFnames() = Array("GCD", "DET")
203+
'
204+
' Evaluator.DeclareUDF UDFnames, "UserDefFunctions" 'Declaring the UDFs. This need
205+
'an instance in the VBAcallBack
206+
'class module.
207+
'
208+
'///////////////////////////////////////////////////////////////////////////////////
209+
actual = GetResult( _
210+
"GCD(1280;240;100;30*cos(0);10*DET({{sin(atn(1)*2); 0; 0}; {0; 2; 0}; {0; 0; 3}}))" _
211+
)
212+
expected = "10"
213+
Assert.AreEqual actual, expected
214+
215+
TestExit:
216+
Exit Sub
217+
TestFail:
218+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
219+
Resume TestExit
220+
End Sub
221+
'@TestMethod("VBA Expressions")
222+
Private Sub LogicalOperatorsNumericOutput()
223+
On Error GoTo TestFail
224+
225+
actual = GetResult( _
226+
"(x<=0)* x^2 + (x>0 & x<=1)* Ln(x+1) + (x>1)* Sqr(x-Ln(2))" _
227+
, "x = 6" _
228+
)
229+
expected = "2.30366074313039"
230+
Assert.AreEqual actual, expected
231+
232+
TestExit:
233+
Exit Sub
234+
TestFail:
235+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
236+
Resume TestExit
237+
End Sub
238+
'@TestMethod("VBA Expressions")
239+
Private Sub TestLogicalOperatorsBooleanOutput()
240+
On Error GoTo TestFail
241+
242+
actual = GetResult( _
243+
"x>0 & Sqr(x-Ln(2))>=3 | tan(x)<0" _
244+
, "x = 6" _
245+
)
246+
expected = "True"
247+
Assert.AreEqual actual, expected
248+
249+
TestExit:
250+
Exit Sub
251+
TestFail:
252+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
253+
Resume TestExit
254+
End Sub

0 commit comments

Comments
 (0)