Skip to content

Commit 15ae924

Browse files
committed
Support for LIKE ($) operator
1 parent 5fbd8e4 commit 15ae924

File tree

1 file changed

+99
-60
lines changed

1 file changed

+99
-60
lines changed

src/CSVexpressions.cls

Lines changed: 99 additions & 60 deletions
Original file line numberDiff line numberDiff line change
@@ -52,28 +52,28 @@ Option Explicit
5252
' Alphabet = "A-Z" | "a-z"
5353
' Decimal = "."
5454
' Digit = "0-9"
55-
' Operator = "+" | "-" | "*" | "/" | "\" | "^" | "%" | "!" | "<" | "<=" | "<>" | ">" | ">=" | "=" | "&" | "|" | "||"
55+
' Operator = "+" | "-" | "*" | "/" | "\" | "^" | "%" | "!" | "<" | "<=" | "<>" | ">" | ">=" | "=" | "$" | "&" | "|" | "||"
5656
' Function = "abs" | "sin" | "cos" | "min" |...|[UDF]
5757
'
5858
'///////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
5959
'#
6060
' ABOUT THE ORDER IN WHICH MATHEMATICAL EXPRESSIONS ARE EVALUATED:
6161
' VBA expressions uses the following precedence rules to evaluate mathematical expressions:
6262
'
63-
' 1. () Grouping: evaluates functions arguments as well.
64-
' 2. ! - + Unary operators: exponentiation is the only operation that violates this. Ex.:
65-
' -2 ^ 2 = -4 | (-2) ^ 2 = 4.
66-
' 3. ^ Exponentiation: Although Excel and Matlab evaluate nested exponentiations from
67-
' left to right, Google, mathematicians and several modern programming languages,
68-
' such as Perl, Python and Ruby, evaluate this operation from right to left.
69-
' VBA expressions also evals in Python way: a^b^c = a^(b^c).
70-
' 4. * / % Multiplication, division, modulo: from left to right.
71-
' 5. + - Addition and subtraction: from left to right.
72-
' 6. < <= <> >= = > Comparison operators.
73-
' 7. ~ Logical negation.
74-
' 8. & Logical AND.
75-
' 9. || Logical XOR.
76-
' 10. | Logical OR.
63+
' 1. () Grouping: evaluates functions arguments as well.
64+
' 2. ! - + Unary operators: exponentiation is the only operation that violates this. Ex.:
65+
' -2 ^ 2 = -4 | (-2) ^ 2 = 4.
66+
' 3. ^ Exponentiation: Although Excel and Matlab evaluate nested exponentiations from
67+
' left to right, Google, mathematicians and several modern programming languages,
68+
' such as Perl, Python and Ruby, evaluate this operation from right to left.
69+
' VBA expressions also evals in Python way: a^b^c = a^(b^c).
70+
' 4. * / % Multiplication, division, modulo: from left to right.
71+
' 5. + - Addition and subtraction: from left to right.
72+
' 6. < <= <> >= = > $ Comparison operators.
73+
' 7. ~ Logical negation.
74+
' 8. & Logical AND.
75+
' 9. || Logical XOR.
76+
' 10. | Logical OR.
7777
'
7878
' Users can enter variables and substitute their values for the calculations. Variable names
7979
' must meet the following requirements:
@@ -136,9 +136,10 @@ Private Const op_gtequal As String = ">="
136136
Private Const op_and As String = "&"
137137
Private Const op_or As String = "|"
138138
Private Const op_xor As String = "||"
139+
Private Const op_like As String = "$"
139140
Private Const op_neg As String = "~"
140-
Private Const op_AllItems As String = "*+-/^%\=<>&|"
141-
Private Const op_AllNotUnaryItems As String = "*/^%\=<>&|"
141+
Private Const op_AllItems As String = "*+-/^%\=<>&|$"
142+
Private Const op_AllNotUnaryItems As String = "*/^%\=<>&|$"
142143
Private Const d_lCurly As String = "{"
143144
Private Const d_rCurly As String = "}"
144145
Private Const d_lParenthesis As String = "("
@@ -175,22 +176,23 @@ Private UserDefFunctions As ClusterBuffer
175176
' ENUMERATIONS:
176177
Public Enum OperatorToken
177178
otNull = 0
178-
otSum = 1 '+
179-
otDiff = 2 '-
180-
otMultiplication = 3 '*
181-
otDivision = 4 '/
182-
otIntDiv = 5 '\
183-
otPower = 6 '^
184-
otMod = 7 '%
185-
otEqual = 8 '=
186-
otNotEqual = 9 '<>
187-
otGreaterThan = 10 '>
188-
otLessThan = 11 '<
189-
otGreaterThanOrEqual = 12 '>=
190-
otLessThanOrEqual = 13 '<=
191-
otLogicalAND = 14 '&
192-
otLogicalOR = 15 '|
193-
otLogicalXOR = 16 '||
179+
otSum = 1 '+
180+
otDiff = 2 '-
181+
otMultiplication = 3 '*
182+
otDivision = 4 '/
183+
otIntDiv = 5 '\
184+
otPower = 6 '^
185+
otMod = 7 '%
186+
otEqual = 101 '=
187+
otNotEqual = 102 '<>
188+
otGreaterThan = 103 '>
189+
otLessThan = 104 '<
190+
otGreaterThanOrEqual = 105 '>=
191+
otLessThanOrEqual = 106 '<=
192+
otLike = 107 '$
193+
otLogicalAND = 201 '&
194+
otLogicalOR = 202 '|
195+
otLogicalXOR = 203 '||
194196
End Enum
195197
Public Enum ExpressionErrors
196198
errNone = 0
@@ -343,8 +345,8 @@ Public Property Get Degrees() As Boolean
343345
Degrees = P_DEGREES
344346
End Property
345347

346-
Public Property Let Degrees(aValue As Boolean)
347-
P_DEGREES = aValue
348+
Public Property Let Degrees(AValue As Boolean)
349+
P_DEGREES = AValue
348350
End Property
349351

350352
''' <summary>
@@ -377,8 +379,8 @@ Public Property Get GallopingMode() As Boolean
377379
GallopingMode = P_GALLOPING_MODE
378380
End Property
379381

380-
Public Property Let GallopingMode(aValue As Boolean)
381-
P_GALLOPING_MODE = aValue
382+
Public Property Let GallopingMode(AValue As Boolean)
383+
P_GALLOPING_MODE = AValue
382384
End Property
383385

384386
''' <summary>
@@ -403,8 +405,8 @@ Public Property Get SeparatorChar() As String
403405
SeparatorChar = P_SEPARATORCHAR
404406
End Property
405407

406-
Public Property Let SeparatorChar(aValue As String)
407-
P_SEPARATORCHAR = aValue
408+
Public Property Let SeparatorChar(AValue As String)
409+
P_SEPARATORCHAR = AValue
408410
End Property
409411

410412
''' <summary>
@@ -442,12 +444,12 @@ Private Function aCeiling(ByRef Expression As String) As Double
442444
aCeiling = Ceiling(CDbl(Expression))
443445
End Function
444446

445-
Public Sub AddConstant(aValue As String, aKey As String)
447+
Public Sub AddConstant(AValue As String, aKey As String)
446448
Dim ConstIdx As Long
447449

448450
ConstIdx = GetCBItemIdx(P_CONSTANTS, aKey)
449451
If ConstIdx = -1 Then 'Ensure uniqueness
450-
AppendToCBbuffer P_CONSTANTS, aKey, aValue
452+
AppendToCBbuffer P_CONSTANTS, aKey, AValue
451453
End If
452454
End Sub
453455

@@ -696,7 +698,7 @@ Private Function average(ByRef Expression As String) As Double
696698
End Function
697699

698700
Private Sub BottomLevelEval(ByRef aToken As Token)
699-
If aToken.OperationToken < 8 Then 'Arithmetic operators
701+
If aToken.OperationToken < 100 Then 'Arithmetic operators
700702
Select Case aToken.OperationToken
701703
Case OperatorToken.otSum
702704
aToken.EvalResult = CastOPtype(aToken.Arg1.Operand, aToken.Arg1.NegationFlagOn) _
@@ -741,7 +743,7 @@ Private Sub BottomLevelEval(ByRef aToken As Token)
741743
End If
742744
End Select
743745
Else
744-
If aToken.OperationToken < 14 Then 'Comparison operators
746+
If aToken.OperationToken < 200 Then 'Comparison operators
745747
Select Case aToken.OperationToken
746748
Case OperatorToken.otEqual
747749
aToken.EvalResult = (CastOPtype(aToken.Arg1.Operand, aToken.Arg1.NegationFlagOn) = _
@@ -758,9 +760,12 @@ Private Sub BottomLevelEval(ByRef aToken As Token)
758760
Case OperatorToken.otGreaterThanOrEqual
759761
aToken.EvalResult = CastOPtype(aToken.Arg1.Operand, aToken.Arg1.NegationFlagOn) >= _
760762
CastOPtype(aToken.Arg2.Operand, aToken.Arg2.NegationFlagOn)
761-
Case Else
763+
Case OperatorToken.otLessThanOrEqual
762764
aToken.EvalResult = CastOPtype(aToken.Arg1.Operand, aToken.Arg1.NegationFlagOn) <= _
763765
CastOPtype(aToken.Arg2.Operand, aToken.Arg2.NegationFlagOn)
766+
Case OperatorToken.otLike
767+
aToken.EvalResult = CastOPtype(aToken.Arg1.Operand, aToken.Arg1.NegationFlagOn) Like _
768+
CastOPtype(aToken.Arg2.Operand, aToken.Arg2.NegationFlagOn)
764769
End Select
765770
Else 'Logical operators
766771
Dim tmpBooleans() As Boolean
@@ -806,8 +811,8 @@ Private Sub CastCase(ByRef Expression As String, ByRef outStr As String)
806811
End Sub
807812

808813
Private Function CastOPtype(ByRef strOperand As String, ByRef Negate As Boolean) As Variant
809-
If InStrB(1, strOperand, d_Apostrophe) Then 'Literal strings like ['string']
810-
CastOPtype = strOperand
814+
If IsLiteralString(strOperand) Then 'Literal strings like ['string']
815+
CastOPtype = FormatLiteralString(strOperand)
811816
Else
812817
If AscW(strOperand) < 58 Then
813818
CastOPtype = CDbl(strOperand)
@@ -1099,6 +1104,9 @@ Private Function Floor(ByRef value As Double) As Double
10991104
Floor = tmpResult + ((value <> tmpResult) And (value < 0))
11001105
End Function
11011106

1107+
Private Function FormatLiteralString(ByRef LiteralString As String) As String
1108+
FormatLiteralString = MidB$(LiteralString, 3, LenB(LiteralString) - 4)
1109+
End Function
11021110
Private Function Gamma(ByRef x As Double) As Double
11031111
'Copyright © 2004, Leonardo Volpi & Foxes Team.
11041112
Dim mantissa As Double, Expo As Double, z As Double
@@ -1176,7 +1184,7 @@ Private Function GetArithOpInfo(ByRef Expression As String) As TokenInfo
11761184
GetArithOpInfo.OperationToken = otPower
11771185
GetArithOpInfo.OperatorLen = LenB(op_power)
11781186
Else
1179-
MultSymbolPos = InStrB(1, Expression, op_mult)
1187+
MultSymbolPos = GetMultSymbolPos(Expression)
11801188
DivSymbolPos = InStrB(1, Expression, op_div)
11811189
IntDivSymbolPos = InStrB(1, Expression, op_intDiv)
11821190
ModSymbolPos = InStrB(1, Expression, op_mod)
@@ -1370,7 +1378,11 @@ Private Function GetEvalToken(ByRef Expression As String) As Token
13701378
GetTokenStart Expression, TokenDet.Position, TokenStart
13711379
'@--------------------------------------------------------------------
13721380
' Find token end
1373-
GetTokenEnd Expression, TokenDet.Position, TokenDet.OperatorLen, TokenEnd
1381+
If TokenDet.OperationToken <> otLike Then
1382+
GetTokenEnd Expression, TokenDet.Position, TokenDet.OperatorLen, TokenEnd
1383+
Else
1384+
GetTokenEnd Expression, InStrB(TokenDet.Position + 4, Expression, d_Apostrophe), TokenDet.OperatorLen, TokenEnd
1385+
End If
13741386
'@--------------------------------------------------------------------
13751387
' Fill token data
13761388
GetEvalToken.DefString = MidB$(Expression, TokenStart, TokenEnd - TokenStart + 2)
@@ -1476,6 +1488,7 @@ Private Function GetLCOpInfo(ByRef Expression As String) As TokenInfo
14761488
Dim LogANDSymbolPos As Long
14771489
Dim LogORSymbolPos As Long
14781490
Dim LogXORSymbolPos As Long
1491+
Dim LikeSymbolPos As Long
14791492
Dim testChar As String
14801493

14811494
'@--------------------------------------------------------------------
@@ -1507,10 +1520,12 @@ Private Function GetLCOpInfo(ByRef Expression As String) As TokenInfo
15071520
Loop While LessThanSymbolPos > 0 And testChar = op_equal
15081521
GreatterOrEqualSymbolPos = InStrB(1, Expression, op_gtequal)
15091522
LessOrEqualSymbolPos = InStrB(1, Expression, op_ltequal)
1523+
LikeSymbolPos = InStrB(LessThanSymbolPos + 1, Expression, op_like)
15101524
If NonZero(EqualSymbolPos, NotEqualSymbolPos, GreatterThanSymbolPos, _
1511-
LessThanSymbolPos, GreatterOrEqualSymbolPos, LessOrEqualSymbolPos) Then
1525+
LessThanSymbolPos, GreatterOrEqualSymbolPos, LessOrEqualSymbolPos, LikeSymbolPos) Then
15121526
GetLCOpInfo.Position = MinNonZero(EqualSymbolPos, NotEqualSymbolPos, GreatterThanSymbolPos, _
1513-
LessThanSymbolPos, GreatterOrEqualSymbolPos, LessOrEqualSymbolPos) 'Priority to the first operator
1527+
LessThanSymbolPos, GreatterOrEqualSymbolPos, LessOrEqualSymbolPos, _
1528+
LikeSymbolPos) 'Priority to the first operator
15141529
Select Case GetLCOpInfo.Position
15151530
Case EqualSymbolPos
15161531
GetLCOpInfo.OperationToken = otEqual
@@ -1527,9 +1542,12 @@ Private Function GetLCOpInfo(ByRef Expression As String) As TokenInfo
15271542
Case GreatterOrEqualSymbolPos
15281543
GetLCOpInfo.OperationToken = otGreaterThanOrEqual
15291544
GetLCOpInfo.OperatorLen = LenB(op_gtequal)
1530-
Case Else
1545+
Case LessOrEqualSymbolPos
15311546
GetLCOpInfo.OperationToken = otLessThanOrEqual
15321547
GetLCOpInfo.OperatorLen = LenB(op_ltequal)
1548+
Case LikeSymbolPos
1549+
GetLCOpInfo.OperationToken = otLike
1550+
GetLCOpInfo.OperatorLen = LenB(op_like)
15331551
End Select
15341552
'@--------------------------------------------------------------------
15351553
' LogicalOperators
@@ -1600,6 +1618,22 @@ Private Function GetLParentPos(ByRef Expression As String, ByRef RelativePositio
16001618
GetLParentPos = tmpResult
16011619
End Function
16021620

1621+
Private Function GetMultSymbolPos(ByRef Expression As String) As Long
1622+
Dim tmpResult As Long
1623+
Dim LStrOpenPos As Long
1624+
Dim LStrClosePos As Long
1625+
1626+
tmpResult = InStrB(1, Expression, op_mult)
1627+
LStrOpenPos = InStrB(1, Expression, d_Apostrophe)
1628+
If LStrOpenPos Then
1629+
LStrClosePos = InStrB(LStrOpenPos + 2, Expression, d_Apostrophe)
1630+
Do While (tmpResult > LStrOpenPos) And (tmpResult < LStrClosePos)
1631+
tmpResult = InStrB(tmpResult + 2, Expression, op_mult)
1632+
Loop
1633+
End If
1634+
GetMultSymbolPos = tmpResult
1635+
End Function
1636+
16031637
Private Sub GetOperand(ByRef CurToken As Token, ByRef CurArg As Argument, _
16041638
ByRef CurTree As ClusterTree, ByRef BaseIndex As Long)
16051639

@@ -1704,6 +1738,8 @@ Private Function GetOpSymbol(ByRef OPtoken As OperatorToken) As String
17041738
GetOpSymbol = op_gtequal
17051739
Case OperatorToken.otLessThanOrEqual
17061740
GetOpSymbol = op_ltequal
1741+
Case OperatorToken.otLike
1742+
GetOpSymbol = op_like
17071743
Case OperatorToken.otLogicalAND
17081744
GetOpSymbol = op_and
17091745
Case OperatorToken.otLogicalOR
@@ -1758,9 +1794,9 @@ Private Sub GetRootedTree(ByRef SubExpression As String, ByRef tmpReplacement As
17581794
Loop While switch
17591795
End Sub
17601796

1761-
Private Function GetSubstStr(ByRef aValue As Long) As String
1762-
If aValue >= 0 Then
1763-
LIndexConstruc(1) = aValue
1797+
Private Function GetSubstStr(ByRef AValue As Long) As String
1798+
If AValue >= 0 Then
1799+
LIndexConstruc(1) = AValue
17641800
GetSubstStr = Join$(LIndexConstruc, vbNullString)
17651801
End If
17661802
End Function
@@ -1894,7 +1930,7 @@ Private Function GetTokenInfo(ByRef Expression As String) As TokenInfo
18941930

18951931
tmpResult = GetArithOpInfo(Expression)
18961932
If tmpResult.Position = -1 Then 'Missing arithmetic opetarators.
1897-
If Expression Like "*[=<>&|]*" Then 'Try with logical operators.
1933+
If Expression Like "*[=<>&|$]*" Then 'Try with logical operators.
18981934
tmpResult = GetLCOpInfo(Expression)
18991935
tmpResult.LogicalToken = True
19001936
Else
@@ -2085,9 +2121,12 @@ Private Function IsLikeSciNot(ByRef Chars As String) As Boolean
20852121
End Function
20862122

20872123
Private Function IsLiteralString(ByRef aString As String) As Boolean
2088-
If LenB(aString) Then
2124+
Dim LenStr As Long
2125+
2126+
LenStr = LenB(aString)
2127+
If LenStr Then
20892128
If AscW(aString) = 39 Then 'Apostrophe
2090-
IsLiteralString = (InStrB(3, aString, d_Apostrophe) = LenB(aString) - 1)
2129+
IsLiteralString = (InStrB(3, aString, d_Apostrophe) = LenStr - 1)
20912130
Else
20922131
IsLiteralString = False
20932132
End If
@@ -2232,14 +2271,14 @@ End Function
22322271
Private Function OPsymbolInArgument(ByRef ArgDefStr As String, ByRef Pattrn As String) As Boolean
22332272
Dim i As Long
22342273
Dim tmpResult As Boolean
2235-
Dim lenStr As Long
2274+
Dim LenStr As Long
22362275

22372276
i = 1
2238-
lenStr = LenB(ArgDefStr)
2277+
LenStr = LenB(ArgDefStr)
22392278
Do
22402279
tmpResult = InStrB(1, MidB$(ArgDefStr, i, 2), Pattrn)
22412280
i = i + 2
2242-
Loop While i <= lenStr And Not tmpResult
2281+
Loop While i <= LenStr And Not tmpResult
22432282
OPsymbolInArgument = tmpResult
22442283
End Function
22452284

0 commit comments

Comments
 (0)