@@ -2212,15 +2212,15 @@ End Function
22122212Public Function Create(ByRef aExpression As Variant, Optional resetScope As Boolean = True) As Object
22132213 If aExpression <> vbNullString Then
22142214 ExprToEval = FormatEntry(CStr(aExpression))
2215- If ExprToEval <> FormatEntry(P_EXPRESSION) Then
2215+ If ( ExprToEval <> FormatEntry(P_EXPRESSION) ) Then
22162216 P_EXPRESSION = aExpression
22172217 If resetScope Then
2218- VariablesInit ExprToEval
2218+ VariablesInit( ExprToEval)
22192219 Else
2220- ParseVariables ExprToEval
2220+ ParseVariables( ExprToEval)
22212221 End If
2222- ExprToEval = SBracketsNotationToNominal(ExprToEval)
2223- Parse ExprToEval
2222+ ExprToEval = SBracketsNotationToNominal(ReplaceImpliedMult( ExprToEval) )
2223+ Parse( ExprToEval)
22242224 End If
22252225 AssignedExpression = True
22262226 End If
@@ -3213,13 +3213,12 @@ Private Function Floor(ByRef value As Double) As Double
32133213End Function
32143214
32153215Private Function FormatEntry(expression As String) As String
3216- FormatEntry = ReplaceImpliedMult( _
3217- Replace( _
3218- RemoveDupNegation( _
3219- ApplyLawOfSigns( _
3220- ReconstructLiteralStrings( _
3221- expression, Join$(Split(expression, d_Space), vbNullString)))), _
3222- " ()" , " ('' )" ))
3216+ FormatEntry = Replace( _
3217+ RemoveDupNegation( _
3218+ ApplyLawOfSigns( _
3219+ ReconstructLiteralStrings( _
3220+ expression, Join$(Split(expression, d_Space), vbNullString)))), _
3221+ " ()" , " ('' )" )
32233222End Function
32243223
32253224Private Function FormatLiteralString(ByRef aString As String, _
@@ -3991,11 +3990,14 @@ Private Function GetFunctionName(ByRef expression As String) As String
39913990 Dim ExpCopy As String
39923991 Dim tmpPos As Long
39933992
3994- ExpCopy = LCase$(expression)
3993+ ExpCopy = Replace(Replace( _
3994+ LCase$(expression),d_lSquareB,d_lCurly,1), _
3995+ d_rSquareB,d_rCurly,1) ' Bypass LO Basic LIKE OP limitation
39953996 For EFjCounter = LBound(FunctionsId) To UBound(FunctionsId)
39963997 tmpPos = strVBA.InStrB(1, ExpCopy, FunctionsId(EFjCounter))
39973998 If tmpPos Then
3998- If ExpCopy = FunctionsId(EFjCounter) Then
3999+ If ExpCopy = FunctionsId(EFjCounter) Or _
4000+ (ExpCopy Like (FunctionsId(EFjCounter) & " {*}" )) Then
39994001 GFNbool = ValidFuntionName(ExpCopy, FunctionsId(EFjCounter), tmpPos)
40004002 If GFNbool Then
40014003 Exit For
@@ -4011,8 +4013,9 @@ Private Function GetFunctionName(ByRef expression As String) As String
40114013 For i = 0 To UserDefFunctions.aindex
40124014 tmpPos = strVBA.InStrB(1, ExpCopy, UserDefFunctions.Storage(i).aName)
40134015 If tmpPos Then
4014- If ExpCopy = UserDefFunctions.Storage(I).name Then
4015- GFNbool = ValidFuntionName(ExpCopy, UserDefFunctions.Storage(I).name, tmpPos)
4016+ If ExpCopy = UserDefFunctions.Storage(I).aname Or _
4017+ (ExpCopy Like (UserDefFunctions.Storage(I).aname & " {*}" )) Then
4018+ GFNbool = ValidFuntionName(ExpCopy, UserDefFunctions.Storage(I).aname, tmpPos)
40164019 If GFNbool Then
40174020 Exit For
40184021 End If
@@ -4023,10 +4026,7 @@ Private Function GetFunctionName(ByRef expression As String) As String
40234026 If GFNbool Then
40244027 GetFunctionName = UserDefFunctions.Storage(i).aName
40254028 Else
4026- ExpCopy = Replace(Replace( _
4027- expression,d_lSquareB,d_lCurly,1), _
4028- d_rSquareB,d_rCurly,1) ' Bypass LO Basic LIKE OP limitation
4029- If (ExpCopy Like " [A-Zaz]*{*}" ) Then ' Not defined function bypass
4029+ If (ExpCopy Like " [A-Za-z]*{*}" ) Then ' Not defined function bypass
40304030 tmpPos = strVBA.InStrB(1, expression, d_lSquareB)
40314031 GetFunctionName = strVBA.MidB(expression, 1, tmpPos - 1)
40324032 End If
@@ -7799,25 +7799,28 @@ Private Function ReplaceImpliedMult(expression As String) As String
77997799 Dim tmpVarInitPos As Long
78007800 Dim prevChar As String
78017801 Dim reservedChar As Boolean
7802+ Dim tmpChar As String
78027803
78037804 LookupPos = 1
78047805 tmpStr = expression
78057806 tmpPos = strVBA.InStrB(LookupPos, tmpStr, d_lParenthesis)
78067807 Do While tmpPos
78077808 If tmpPos > 2 Then
7808- If InStr (1, op_AllItems, strVBA.MidB(tmpStr, tmpPos - 2, 2)) = 0 Then
7809+ If strVBA.InStrB (1, op_AllItems, strVBA.MidB(tmpStr, tmpPos - 2, 2)) = 0 Then
78097810 tmpVarInitPos = tmpPos
78107811 Do While tmpVarInitPos > 1
7811- If (strVBA.InStrB(1, op_AllItems, strVBA.MidB(tmpStr, tmpVarInitPos - 2, 2)) <> 0) Then
7812- Exit Do
7813- End If
7812+ tmpChar = strVBA.MidB(tmpStr, tmpVarInitPos - 2, 2)
7813+ If (strVBA.InStrB(1, op_AllItems, tmpChar) <> 0) Then Exit Do
7814+ If tmpChar = d_lParenthesis Then Exit Do
7815+ If tmpChar = d_rParenthesis Then Exit Do
7816+ If tmpChar = P_SEPARATORCHAR Then Exit Do
78147817 tmpVarInitPos = tmpVarInitPos - 2
78157818 Loop
78167819 tmpVar = strVBA.MidB(tmpStr, tmpVarInitPos, tmpPos - tmpVarInitPos)
78177820 prevChar = strVBA.MidB(tmpStr, tmpPos - 2, 2)
78187821 reservedChar = (prevChar = d_lParenthesis Or strVBA.InStrB(1, op_AllItems, prevChar))
78197822 If Not reservedChar Then
7820- If GetFunctionName(LCase$ (tmpVar)) = vbNullString Then ' Implied multiplication found
7823+ If GetFunctionName(LCase(tmpVar)) = vbNullString Then ' Implied multiplication found
78217824 tmpStr = strVBA.MidB(tmpStr, 1, tmpPos - 1) & op_mult & strVBA.MidB(tmpStr, tmpPos)
78227825 End If
78237826 End If
0 commit comments