Skip to content

Commit 4864334

Browse files
committed
v3.2.6
1 parent feb557c commit 4864334

File tree

4 files changed

+63
-41
lines changed

4 files changed

+63
-41
lines changed

src/LO Basic/VBAExpressions.update.xml

Whitespace-only changes.

src/LO Basic/VBAExpressionsLib/TestVBAExpr.xba

Lines changed: 17 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -342,6 +342,11 @@ Sub RunAllTests
342342
"ROUND(TINV(0.75;2;1);8)", _
343343
"0.81649658" _
344344
)
345+
Run( _
346+
"IRR_ function test", _
347+
"FORMAT(IRR({{-70000;12000;15000}};true);'Percent')", _
348+
"'-44.35%'" _
349+
)
345350
SF_Exception.debugprint("Passed tests:",sAcum)
346351
SF_Exception.debugprint("Failed tests:",tTotal - sAcum)
347352
SF_Exception.debugprint("Passed tests Ratio:",Round(100*sAcum/tTotal,2) &"%")
@@ -454,10 +459,20 @@ TestFail:
454459
SF_Exception.debugprint("Test " & testName & " raised an error: #" & err.Number & " - " & err.Description)
455460
Resume TestExit
456461
End Sub
457-
sub tesover
462+
sub testOver
458463
'msgbox ("a{2}" Like "[A-Zaz]*{*}")
459464
SF_Exception.consoleClear()
460-
call VarOverload("Variables overloading: indirect assignment")
465+
' Run( _
466+
' "IRR_ function test", _
467+
' "FORMAT(IRR({{-70000;12000;15000}};true);'Percent')", _
468+
' "'-44.35%'" _
469+
' )
470+
Run( _
471+
"Variables overloading", _
472+
"SUM(C[0;0];C[1;1])", _
473+
"14", _
474+
"C = {{-1;13};{6;15}}" _
475+
)
461476
SF_Exception.console()
462477
end sub
463478
</script:module>

src/LO Basic/VBAExpressionsLib/VBAexpressions.xba

Lines changed: 28 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -2212,15 +2212,15 @@ End Function
22122212
Public Function Create(ByRef aExpression As Variant, Optional resetScope As Boolean = True) As Object
22132213
If aExpression &lt;&gt; vbNullString Then
22142214
ExprToEval = FormatEntry(CStr(aExpression))
2215-
If ExprToEval &lt;&gt; FormatEntry(P_EXPRESSION) Then
2215+
If (ExprToEval &lt;&gt; 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
32133213
End Function
32143214

32153215
Private 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-
&quot;()&quot;, &quot;(&apos;&apos;)&quot;))
3216+
FormatEntry = Replace( _
3217+
RemoveDupNegation( _
3218+
ApplyLawOfSigns( _
3219+
ReconstructLiteralStrings( _
3220+
expression, Join$(Split(expression, d_Space), vbNullString)))), _
3221+
&quot;()&quot;, &quot;(&apos;&apos;)&quot;)
32233222
End Function
32243223

32253224
Private 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) &apos;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) &amp; &quot;{*}&quot;)) 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 &amp; &quot;{*}&quot;)) 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) &apos;Bypass LO Basic LIKE OP limitation
4029-
If (ExpCopy Like &quot;[A-Zaz]*{*}&quot;) Then &apos;Not defined function bypass
4029+
If (ExpCopy Like &quot;[A-Za-z]*{*}&quot;) Then &apos;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 &gt; 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 &gt; 1
7811-
If (strVBA.InStrB(1, op_AllItems, strVBA.MidB(tmpStr, tmpVarInitPos - 2, 2)) &lt;&gt; 0) Then
7812-
Exit Do
7813-
End If
7812+
tmpChar = strVBA.MidB(tmpStr, tmpVarInitPos - 2, 2)
7813+
If (strVBA.InStrB(1, op_AllItems, tmpChar) &lt;&gt; 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 &apos;Implied multiplication found
7823+
If GetFunctionName(LCase(tmpVar)) = vbNullString Then &apos;Implied multiplication found
78217824
tmpStr = strVBA.MidB(tmpStr, 1, tmpPos - 1) &amp; op_mult &amp; strVBA.MidB(tmpStr, tmpPos)
78227825
End If
78237826
End If

src/VBAexpressions.cls

Lines changed: 18 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -2241,7 +2241,7 @@ Public Function Create(ByRef aExpression As Variant, Optional resetScope As Bool
22412241
Else
22422242
ParseVariables ExprToEval
22432243
End If
2244-
ExprToEval = SBracketsNotationToNominal(ExprToEval)
2244+
ExprToEval = SBracketsNotationToNominal(ReplaceImpliedMult(ExprToEval))
22452245
Parse ExprToEval
22462246
End If
22472247
AssignedExpression = True
@@ -3121,13 +3121,12 @@ Private Function Floor(ByRef value As Double) As Double
31213121
End Function
31223122

31233123
Private Function FormatEntry(expression As String) As String
3124-
FormatEntry = ReplaceImpliedMult( _
3125-
Replace( _
3126-
RemoveDupNegation( _
3127-
ApplyLawOfSigns( _
3128-
ReconstructLiteralStrings( _
3129-
expression, Join$(Split(expression, d_Space), vbNullString)))), _
3130-
"()", "('')"))
3124+
FormatEntry = Replace( _
3125+
RemoveDupNegation( _
3126+
ApplyLawOfSigns( _
3127+
ReconstructLiteralStrings( _
3128+
expression, Join$(Split(expression, d_Space), vbNullString)))), _
3129+
"()", "('')")
31313130
End Function
31323131

31333132
Private Function FormatLiteralString(ByRef aString As String, _
@@ -3897,7 +3896,8 @@ Private Function GetFunctionName(ByRef expression As String) As String
38973896
For EFjCounter = LBound(FunctionsId) To UBound(FunctionsId)
38983897
tmpPos = InStrB(1, ExpCopy, FunctionsId(EFjCounter))
38993898
If tmpPos Then
3900-
If ExpCopy = FunctionsId(EFjCounter) Then
3899+
If ExpCopy = FunctionsId(EFjCounter) Or _
3900+
(ExpCopy Like FunctionsId(EFjCounter) & "[[]*[]]") Then
39013901
GFNbool = ValidFuntionName(ExpCopy, FunctionsId(EFjCounter), tmpPos)
39023902
If GFNbool Then
39033903
Exit For
@@ -3913,7 +3913,8 @@ Private Function GetFunctionName(ByRef expression As String) As String
39133913
For I = 0 To UserDefFunctions.index
39143914
tmpPos = InStrB(1, ExpCopy, UserDefFunctions.Storage(I).name)
39153915
If tmpPos Then
3916-
If ExpCopy = UserDefFunctions.Storage(I).name Then
3916+
If ExpCopy = UserDefFunctions.Storage(I).name Or _
3917+
(ExpCopy Like UserDefFunctions.Storage(I).name & "[[]*[]]") Then
39173918
GFNbool = ValidFuntionName(ExpCopy, UserDefFunctions.Storage(I).name, tmpPos)
39183919
If GFNbool Then
39193920
Exit For
@@ -3925,7 +3926,7 @@ Private Function GetFunctionName(ByRef expression As String) As String
39253926
If GFNbool Then
39263927
GetFunctionName = UserDefFunctions.Storage(I).name
39273928
Else
3928-
If expression Like "[A-Zaz]*[[]*[]]" Then 'Not defined function bypass
3929+
If expression Like "[A-Za-z]*[[]*[]]" Then 'Not defined function bypass
39293930
tmpPos = InStrB(1, expression, d_lSquareB)
39303931
GetFunctionName = MidB$(expression, 1, tmpPos - 1)
39313932
End If
@@ -7669,6 +7670,7 @@ Private Function ReplaceImpliedMult(expression As String) As String
76697670
Dim tmpVarInitPos As Long
76707671
Dim prevChar As String
76717672
Dim reservedChar As Boolean
7673+
Dim tmpChar As String
76727674

76737675
LookupPos = 1
76747676
tmpStr = expression
@@ -7678,9 +7680,11 @@ Private Function ReplaceImpliedMult(expression As String) As String
76787680
If InStr(1, op_AllItems, MidB(tmpStr, tmpPos - 2, 2)) = 0 Then
76797681
tmpVarInitPos = tmpPos
76807682
Do While tmpVarInitPos > 1
7681-
If (InStrB(1, op_AllItems, MidB$(tmpStr, tmpVarInitPos - 2, 2)) <> 0) Then
7682-
Exit Do
7683-
End If
7683+
tmpChar = MidB$(tmpStr, tmpVarInitPos - 2, 2)
7684+
If (InStrB(1, op_AllItems, tmpChar) <> 0) Then Exit Do
7685+
If tmpChar = d_lParenthesis Then Exit Do
7686+
If tmpChar = d_rParenthesis Then Exit Do
7687+
If tmpChar = P_SEPARATORCHAR Then Exit Do
76847688
tmpVarInitPos = tmpVarInitPos - 2
76857689
Loop
76867690
tmpVar = MidB$(tmpStr, tmpVarInitPos, tmpPos - tmpVarInitPos)

0 commit comments

Comments
 (0)