Skip to content

Commit 57be52b

Browse files
committed
Fixed error: work with consecutive parentheses was broken.
1 parent b8ea6d3 commit 57be52b

File tree

2 files changed

+16
-10
lines changed

2 files changed

+16
-10
lines changed

src/VBAexpressions.cls

Lines changed: 16 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -2541,7 +2541,7 @@ Private Sub GetRootedTree(ByRef SubExpression As String, ByRef tmpReplacement As
25412541
Dim Switch As Boolean
25422542
Dim tmpPos As Long
25432543
Dim OperandInBundle As Boolean
2544-
Dim PrevChar As String
2544+
Dim prevChar As String
25452545

25462546
Do
25472547
SubExpression = ApplyLawOfSigns(SubExpression)
@@ -2550,12 +2550,12 @@ Private Sub GetRootedTree(ByRef SubExpression As String, ByRef tmpReplacement As
25502550
' Mask worked token
25512551
tmpPos = InStrB(1, SubExpression, vToken.DefString)
25522552
If tmpPos > 2 Then
2553-
PrevChar = MidB$(SubExpression, tmpPos - 2, 2)
2554-
OperandInBundle = (InStrB(1, op_AllItems, PrevChar))
2553+
prevChar = MidB$(SubExpression, tmpPos - 2, 2)
2554+
OperandInBundle = (InStrB(1, op_AllItems, prevChar))
25552555
Do While Not OperandInBundle And tmpPos > 2 'Tokens starts with a operator or with a null string
25562556
tmpPos = InStrB(tmpPos + 2, SubExpression, vToken.DefString)
2557-
PrevChar = MidB$(SubExpression, tmpPos - 2, 2)
2558-
OperandInBundle = (InStrB(1, op_AllItems, PrevChar))
2557+
prevChar = MidB$(SubExpression, tmpPos - 2, 2)
2558+
OperandInBundle = (InStrB(1, op_AllItems, prevChar))
25592559
Loop
25602560
End If
25612561
If tmpPos > 0 Then
@@ -2773,9 +2773,9 @@ Private Sub GetTokenStart(ByRef expression As String, ByRef startIndex As Long,
27732773
If outLng > 1 Then
27742774
Select Case AscW(curChar)
27752775
Case 45, 126
2776-
Dim PrevChar As String
2777-
PrevChar = MidB$(expression, outLng - 2, 2)
2778-
If InStrB(1, op_AllNotUnaryItems, PrevChar) Then
2776+
Dim prevChar As String
2777+
prevChar = MidB$(expression, outLng - 2, 2)
2778+
If InStrB(1, op_AllNotUnaryItems, prevChar) Then
27792779
outLng = outLng - 2
27802780
Else
27812781
outLng = outLng + 2
@@ -4227,6 +4227,8 @@ Private Function ReplaceImpliedMult(expression As String) As String
42274227
Dim LookupPos As Long
42284228
Dim tmpVar As String
42294229
Dim tmpVarInitPos As Long
4230+
Dim prevChar As String
4231+
Dim reservedChar As Boolean
42304232

42314233
LookupPos = 1
42324234
tmpStr = expression
@@ -4242,8 +4244,12 @@ Private Function ReplaceImpliedMult(expression As String) As String
42424244
tmpVarInitPos = tmpVarInitPos - 2
42434245
Loop
42444246
tmpVar = MidB$(tmpStr, tmpVarInitPos, tmpPos - tmpVarInitPos)
4245-
If GetFunctionName(LCase$(tmpVar)) = vbNullString Then 'Implied multiplication found
4246-
tmpStr = MidB(tmpStr, 1, tmpPos - 1) & op_mult & MidB(tmpStr, tmpPos)
4247+
prevChar = MidB$(tmpStr, tmpPos - 2, 2)
4248+
reservedChar = (prevChar = d_lParenthesis Or InStrB(1, op_AllItems, prevChar))
4249+
If Not reservedChar Then
4250+
If GetFunctionName(LCase$(tmpVar)) = vbNullString Then 'Implied multiplication found
4251+
tmpStr = MidB(tmpStr, 1, tmpPos - 1) & op_mult & MidB(tmpStr, tmpPos)
4252+
End If
42474253
End If
42484254
End If
42494255
LookupPos = tmpPos + 4

testing/tests/Test runner.xlsm

40.5 KB
Binary file not shown.

0 commit comments

Comments
 (0)