Skip to content

Commit 2465c3a

Browse files
committed
Revert FZERO function changes.
The scope isn't handled correctly and values for variables disappear between calls. LibreOffice users must perform calculations on univariate functions.
1 parent 0ca51f9 commit 2465c3a

File tree

3 files changed

+55
-15
lines changed

3 files changed

+55
-15
lines changed

src/LO Basic/VBAExpressionsLib/TestRunner.xba

Lines changed: 48 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -576,6 +576,54 @@ Private Sub VALIDATEcircleTangents(testName As String)
576576
SF_Exception.debugprint("+ Success test " & testName)
577577
End If
578578

579+
TestExit:
580+
Exit Sub
581+
TestFail:
582+
SF_Exception.debugprint("Test " & testName & " raised an error: #" & err.Number & " - " & err.Description)
583+
Resume TestExit
584+
End Sub
585+
586+
Private Sub LargestSquareInRATriangle(testName As String)
587+
On Error GoTo TestFail
588+
Dim expect As String
589+
Dim contFunct As String
590+
591+
tTotal=tTotal+1
592+
Set Evaluator = New VBAexpressions
593+
contFunct = "FZERO('GET(_side_;DISTANCE(LINESINTERSECT(" _
594+
& "PERPENDICULAR(hyp;{{x;0}});hyp)" _
595+
& ";{{x;0}}))" _
596+
& "-" _
597+
& "DISTANCE(LINESINTERSECT(" _
598+
& "PERPENDICULAR(PERPENDICULAR(" _
599+
& "hyp;{{x;0}})" _
600+
& ";{{x;0}})" _
601+
& ";leg.a)" _
602+
& ";{{x;0}})'" _
603+
& ";0;12)"
604+
With Evaluator
605+
'Triangle hypotenuse
606+
.Create "GET('hyp';{{12;0};{0;5}})": .Eval
607+
'Leg a definition
608+
.Create "GET(_leg.a_;{{0;0};{0;5}})", False: .Eval
609+
.Create contFunct, False: .Eval
610+
actual = .result
611+
If .ErrorType = 0 Then
612+
.Create "ROUND(side^2;4)", False: .Eval
613+
If .ErrorType = 0 Then
614+
actual .result
615+
End If
616+
End If
617+
End With
618+
expect = "11.6016"
619+
620+
If expect <> actual Then
621+
SF_Exception.debugprint("x Failed test " & testName, expect,"<>",actual)
622+
Else
623+
sAcum=sAcum+1
624+
SF_Exception.debugprint("+ Success test " & testName)
625+
End If
626+
579627
TestExit:
580628
Exit Sub
581629
TestFail:

src/LO Basic/VBAExpressionsLib/VBAexpressions.xba

Lines changed: 4 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -3760,8 +3760,6 @@ End Function
37603760
''' <summary>
37613761
''' Finds a zero of a univariate function ussing a modified bisection method.
37623762
''' aFunction must be a continuous function f(x) for the interval a <= x <= b.
3763-
''' The function zeroing will be performed on the unassigned variable. If more
3764-
''' than one variables are unassigned, an error will be returned.
37653763
''' </summary>
37663764
''' <param name="aFunction">Inline function.</param>
37673765
''' <param name="a">Leftmost interval value.</param>
@@ -3795,16 +3793,13 @@ Private Function fZeroMBM(ByRef aFunction As String, ByVal A As Double, _
37953793
aZero = 10 * epsilon
37963794
With fEvalHelper
37973795
.Create aFunction
3798-
Set .EvalScope = .EvalScope.CopyScope(P_SCOPE)
37993796
tmpVar() = Split(.CurrentVariables, "; ")
38003797
varLB = LBound(tmpVar)
3801-
If UBound(tmpVar) - varLB > 0 Then 'Check multivariate functions
3798+
If UBound(tmpVar) - varLB > 0 Then 'Reject multivariate functions
38023799
For i = varLB To UBound(tmpVar)
38033800
If Not IsConstant(tmpVar(i)) Then
3804-
If Not IsAssigned(tmpVar(i)) Then
3805-
varCounter = varCounter + 1
3806-
varIdx = i
3807-
End If
3801+
varCounter = varCounter + 1
3802+
varIdx = i
38083803
End If
38093804
Next i
38103805
If varCounter > 1 Then
@@ -3865,16 +3860,13 @@ Private Function fZeroMBM(ByRef aFunction As String, ByVal A As Double, _
38653860
.LetVarValue(tmpVar(varIdx), tmpResult)
38663861
If Round(tmpFzeroEval, Len(CStr(1 / aZero)) - 1) = 0 Then
38673862
If includeVarNames Then
3868-
fZeroMBM = ToLiteralString( _
3869-
tmpVar(varIdx) & d_Space & op_equal _
3870-
& d_Space & tmpResult)
3863+
fZeroMBM = ToLiteralString(.CurrentVarValues)
38713864
Else
38723865
fZeroMBM = tmpResult
38733866
End If
38743867
Else
38753868
fZeroMBM = e_ValueError
38763869
End If
3877-
Set P_SCOPE = .EvalScope.CopyToScope
38783870
End With
38793871
fZeroMBM_terminate:
38803872
Set fEvalHelper = Nothing
Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,10 @@
11
<?xml version="1.0" encoding="UTF-8"?>
22
<!DOCTYPE library:library PUBLIC "-//OpenOffice.org//DTD OfficeDocument 1.0//EN" "library.dtd">
33
<library:library xmlns:library="http://openoffice.org/2000/library" library:name="VBAExpressionsLib" library:readonly="false" library:passwordprotected="false">
4-
<library:element library:name="VBAexpressionsScope"/>
5-
<library:element library:name="UDFunctions"/>
64
<library:element library:name="VBAcallBack"/>
7-
<library:element library:name="VBAstrHelper"/>
5+
<library:element library:name="UDFunctions"/>
6+
<library:element library:name="VBAexpressionsScope"/>
87
<library:element library:name="VBAexpressions"/>
8+
<library:element library:name="VBAstrHelper"/>
99
<library:element library:name="TestRunner"/>
1010
</library:library>

0 commit comments

Comments
 (0)