Skip to content

Commit 68f03bc

Browse files
committed
Improvement: ability to compare literal strings given in expressions.
1 parent 7c5eb31 commit 68f03bc

File tree

5 files changed

+29
-2
lines changed

5 files changed

+29
-2
lines changed

README.md

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ Token = [{Unary}] Argument [(Operator | Function) ["("] [{Unary}] [A
3737
Argument = (List | Variable | Operand)
3838
List = "{" ["{"] SubExpr [{";" SubExpr}] ["}"] "}"
3939
Unary = "-" | "+" | ~
40-
Operand = ({Digit} ["."] [{Digit}] ["E"("-" | "+"){Digit}] | (True | False))
40+
Operand = ({Digit} ["."] [{Digit}] ["E"("-" | "+"){Digit}] | (True | False) | "'"Alphabet"'")
4141
Variable = Alphabet [{Decimal}] [{(Digit | Alphabet)}]
4242
Alphabet = "A-Z" | "a-z"
4343
Decimal = "."
@@ -162,6 +162,15 @@ Sub TrigFunctions()
162162
End If
163163
End With
164164
End Sub
165+
Sub StringComp()
166+
Dim Evaluator As VBAexpressions
167+
Set Evaluator = New VBAexpressions
168+
169+
With Evaluator
170+
.Create "Region = 'Central America'" 'Create a expression with `Region` as variable
171+
.Eval ("Region = 'Asia'") 'Assign value to variable and then evaluate
172+
End With
173+
End Sub
165174
```
166175

167176
## Licence
-6.47 KB
Loading

src/Tests/TestRunner.bas

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -284,3 +284,21 @@ TestFail:
284284
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
285285
Resume TestExit
286286
End Sub
287+
'@TestMethod("VBA Expressions")
288+
Private Sub testStringComp()
289+
On Error GoTo TestFail
290+
291+
actual = GetResult( _
292+
"Region = 'Central America'" _
293+
, "Region = 'Asia'" _
294+
)
295+
expected = "False"
296+
Assert.AreEqual expected, actual
297+
298+
TestExit:
299+
Exit Sub
300+
TestFail:
301+
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
302+
Resume TestExit
303+
End Sub
304+

src/VBAexpressions.cls

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ Option Explicit
4747
' Argument = (List | Variable | Operand)
4848
' List = "{" ["{"] SubExpr [{";" SubExpr}] ["}"] "}"
4949
' Unary = "-" | "+" | ~
50-
' Operand = ({Digit} ["."] [{Digit}] ["E"("-" | "+"){Digit}] | (True | False))
50+
' Operand = ({Digit} ["."] [{Digit}] ["E"("-" | "+"){Digit}] | (True | False) | "'"Alphabet"'")
5151
' Variable = Alphabet [{Decimal}] [{(Digit | Alphabet)}]
5252
' Alphabet = "A-Z" | "a-z"
5353
' Decimal = "."

testing/tests/Test runner.xlsm

-163 Bytes
Binary file not shown.

0 commit comments

Comments
 (0)