Skip to content

Commit

Permalink
v3.2.4
Browse files Browse the repository at this point in the history
  • Loading branch information
ws-garcia committed Apr 11, 2024
1 parent 5233374 commit 0d7bc74
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 8 deletions.
12 changes: 11 additions & 1 deletion src/LO Basic/VBAExpressionsLib/TestVBAExpr.xba
Original file line number Diff line number Diff line change
Expand Up @@ -332,7 +332,11 @@ Sub RunAllTests
"C = {{-1;13};{6;15}}" _
)
VarOverload("Variables overloading: indirect assignment")

Run( _
"Excel BETA.DIST function test", _
"ROUND(IBETA((2-1)/(3-1);8;10);4)", _
"0.6855" _
)
SF_Exception.debugprint("Passed tests:",sAcum)
SF_Exception.debugprint("Failed tests:",tTotal - sAcum)
SF_Exception.debugprint("Passed tests Ratio:",Round(100*sAcum/tTotal,2) &"%")
Expand Down Expand Up @@ -445,4 +449,10 @@ TestFail:
SF_Exception.debugprint("Test " & testName & " raised an error: #" & err.Number & " - " & err.Description)
Resume TestExit
End Sub
sub tesover
'msgbox ("a{2}" Like "[A-Zaz]*{*}")
SF_Exception.consoleClear()
call VarOverload("Variables overloading: indirect assignment")
SF_Exception.console()
end sub
</script:module>
17 changes: 10 additions & 7 deletions src/LO Basic/VBAExpressionsLib/VBAexpressions.xba
Original file line number Diff line number Diff line change
Expand Up @@ -341,8 +341,8 @@ Private Sub Class_Initialize()
InitCBbuffer UserDefFunctions
&apos;@--------------------------------------------------------------------
&apos; Populate linked index constructor
LIndexConstruc(0) = d_lCurly
LIndexConstruc(2) = d_rCurly
LIndexConstruc(0) = d_lSquareB
LIndexConstruc(2) = d_rSquareB
&apos;@--------------------------------------------------------------------
&apos; Populate building UDFs
Dim UDFnames() As Variant
Expand Down Expand Up @@ -4019,8 +4019,11 @@ Private Function GetFunctionName(ByRef expression As String) As String
If GFNbool Then
GetFunctionName = UserDefFunctions.Storage(i).aName
Else
If expression Like &quot;[A-Zaz]*{*}&quot; Then &apos;Not defined function bypass
tmpPos = strVBA.InStrB(1, expression, d_lCurly)
ExpCopy = Replace(Replace( _
expression,d_lSquareB,d_lCurly,1), _
d_rSquareB,d_rCurly,1) &apos;Bypass LO Basic LIKE OP limitation
If (ExpCopy Like &quot;[A-Zaz]*{*}&quot;) Then &apos;Not defined function bypass
tmpPos = strVBA.InStrB(1, expression, d_lSquareB)
GetFunctionName = strVBA.MidB(expression, 1, tmpPos - 1)
End If
End If
Expand All @@ -4031,9 +4034,9 @@ Private Function GetIndex(ByRef SubstStr As String) As Long
Dim InitPos As Long
Dim EndPos As Long

InitPos = strVBA.InStrB(1, SubstStr, d_lCurly)
InitPos = strVBA.InStrB(1, SubstStr, d_lSquareB)
If InitPos Then
EndPos = strVBA.InStrB(1, SubstStr, d_rCurly)
EndPos = strVBA.InStrB(1, SubstStr, d_rSquareB)
If EndPos Then
GetIndex = strVBA.MidB(SubstStr, InitPos + 2, EndPos - InitPos - 2)
Else
Expand Down Expand Up @@ -4563,7 +4566,7 @@ End Function

&apos;&apos;&apos; &lt;summary&gt;
&apos;&apos;&apos; Returns an array with all the sub expressions needed to
&apos;&apos;&apos; evaluate the given expression. A string such as {0}
&apos;&apos;&apos; evaluate the given expression. A string such as [0]
&apos;&apos;&apos; indicates that the current token should be evaluated using
&apos;&apos;&apos; the value or token residing at index 0 using functions
&apos;&apos;&apos; and arithmetic operators.
Expand Down

0 comments on commit 0d7bc74

Please sign in to comment.