Skip to content

Commit

Permalink
Fixed error: work with consecutive parentheses was broken.
Browse files Browse the repository at this point in the history
  • Loading branch information
ws-garcia committed Jan 12, 2023
1 parent b8ea6d3 commit 57be52b
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 10 deletions.
26 changes: 16 additions & 10 deletions src/VBAexpressions.cls
Original file line number Diff line number Diff line change
Expand Up @@ -2541,7 +2541,7 @@ Private Sub GetRootedTree(ByRef SubExpression As String, ByRef tmpReplacement As
Dim Switch As Boolean
Dim tmpPos As Long
Dim OperandInBundle As Boolean
Dim PrevChar As String
Dim prevChar As String

Do
SubExpression = ApplyLawOfSigns(SubExpression)
Expand All @@ -2550,12 +2550,12 @@ Private Sub GetRootedTree(ByRef SubExpression As String, ByRef tmpReplacement As
' Mask worked token
tmpPos = InStrB(1, SubExpression, vToken.DefString)
If tmpPos > 2 Then
PrevChar = MidB$(SubExpression, tmpPos - 2, 2)
OperandInBundle = (InStrB(1, op_AllItems, PrevChar))
prevChar = MidB$(SubExpression, tmpPos - 2, 2)
OperandInBundle = (InStrB(1, op_AllItems, prevChar))
Do While Not OperandInBundle And tmpPos > 2 'Tokens starts with a operator or with a null string
tmpPos = InStrB(tmpPos + 2, SubExpression, vToken.DefString)
PrevChar = MidB$(SubExpression, tmpPos - 2, 2)
OperandInBundle = (InStrB(1, op_AllItems, PrevChar))
prevChar = MidB$(SubExpression, tmpPos - 2, 2)
OperandInBundle = (InStrB(1, op_AllItems, prevChar))
Loop
End If
If tmpPos > 0 Then
Expand Down Expand Up @@ -2773,9 +2773,9 @@ Private Sub GetTokenStart(ByRef expression As String, ByRef startIndex As Long,
If outLng > 1 Then
Select Case AscW(curChar)
Case 45, 126
Dim PrevChar As String
PrevChar = MidB$(expression, outLng - 2, 2)
If InStrB(1, op_AllNotUnaryItems, PrevChar) Then
Dim prevChar As String
prevChar = MidB$(expression, outLng - 2, 2)
If InStrB(1, op_AllNotUnaryItems, prevChar) Then
outLng = outLng - 2
Else
outLng = outLng + 2
Expand Down Expand Up @@ -4227,6 +4227,8 @@ Private Function ReplaceImpliedMult(expression As String) As String
Dim LookupPos As Long
Dim tmpVar As String
Dim tmpVarInitPos As Long
Dim prevChar As String
Dim reservedChar As Boolean

LookupPos = 1
tmpStr = expression
Expand All @@ -4242,8 +4244,12 @@ Private Function ReplaceImpliedMult(expression As String) As String
tmpVarInitPos = tmpVarInitPos - 2
Loop
tmpVar = MidB$(tmpStr, tmpVarInitPos, tmpPos - tmpVarInitPos)
If GetFunctionName(LCase$(tmpVar)) = vbNullString Then 'Implied multiplication found
tmpStr = MidB(tmpStr, 1, tmpPos - 1) & op_mult & MidB(tmpStr, tmpPos)
prevChar = MidB$(tmpStr, tmpPos - 2, 2)
reservedChar = (prevChar = d_lParenthesis Or InStrB(1, op_AllItems, prevChar))
If Not reservedChar Then
If GetFunctionName(LCase$(tmpVar)) = vbNullString Then 'Implied multiplication found
tmpStr = MidB(tmpStr, 1, tmpPos - 1) & op_mult & MidB(tmpStr, tmpPos)
End If
End If
End If
LookupPos = tmpPos + 4
Expand Down
Binary file modified testing/tests/Test runner.xlsm
Binary file not shown.

0 comments on commit 57be52b

Please sign in to comment.