@@ -119,7 +119,7 @@ Option Base 0
119119'
120120'///////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
121121' CONSTANTS:
122- Private PI As Double
122+ Private pi As Double
123123Private PID2 As Double
124124Private e As Double
125125Private Const op_plus As String = "+"
@@ -306,9 +306,9 @@ End Type
306306''' </summary>
307307Private Sub Class_Initialize ()
308308 AssignedExpression = False
309- PI = 4 * Atn(1 )
310- PID2 = PI / 2
311- e = Exp (1 )
309+ pi = 4 * Atn(1 )
310+ PID2 = pi / 2
311+ e = exp (1 )
312312 P_SEPARATORCHAR = d_Semicolon
313313 P_DEC_SYMBOL = dsDot
314314 AscDecSymbol = 46
@@ -317,7 +317,7 @@ Private Sub Class_Initialize()
317317 BuildinFunctIDList = "abs;floor;achisq;asin;acos;aerf;afishf;agauss;asc;anorm;atn;astudt;array;avg;beta.dist" & _
318318 ";betainv;ceil;chisq;cholesky;cholinverse;cholsolve;chr;cos;choose;date;dateadd;datediff" & _
319319 ";datepart;dateserial;datevalue;day;ddb;det;erf;exp;fishf;fit;format;fv;fzero" & _
320- ";gamma;gammaln;gauss;get;hour;ibeta;iff;inverse;ipmt;irr;lcase;left;len;log;lgn" & _
320+ ";gamma;gammaln;gauss;get;hour;ibeta;iff;instr; inverse;ipmt;irr;lcase;left;len;log;lgn" & _
321321 ";ln;lsqrsolve;ludecomp;lusolve;max;mid;min;minute;mirr;mlr;mmult;mneg;mround" & _
322322 ";msum;mtranspose;month;monthname;norm;now;nper;npv;percent;pmt;ppmt;pow;pv" & _
323323 ";qr;rate;rem;replace;right;round;sgn;sin;sln;solve;sqr;sqrt;sum;studt;switch" & _
@@ -327,7 +327,7 @@ Private Sub Class_Initialize()
327327 ";ASTUDT;strArray;Average;Beta_Distribution;BETAINV;aCeiling;CHISQ;CholeskyDec;CholeskyInverseMatrix" & _
328328 ";CholeskySolve;ASCIIchr;Cosin;aChoose;aDate;aDateAdd;aDateDiff;aDatePart;aDateSerial" & _
329329 ";aDateValue;aDay;aDDB;MatrixDeterminant;ERF;ExpEuler;FISHF;CurveFit" & _
330- ";aFormat;aFV;FunctionZero;Gamma;GammaLN;GAUSS;GET;aHour;iBETA;aIff;InverseMatrix" & _
330+ ";aFormat;aFV;FunctionZero;Gamma;GammaLN;GAUSS;GET;aHour;iBETA;aIff;aInstr; InverseMatrix" & _
331331 ";aIPMT;aIRR;LowerCase;aLeft;aLen;Logarithm;LgN;LN;LSQRsolve;LUdecomposition" & _
332332 ";LUSolveLinearSystem;Max;Middle;Min;aMinute;aMIRR;MultiLinearReg;MatrixMult" & _
333333 ";MatrixNegation;MatrixRound;MatrixSum;MatrixTranspose;aMonth;aMonthName;NORM" & _
@@ -1099,7 +1099,7 @@ Private Function ArcCos(ByRef expression As String, ByRef fName As String) As St
10991099 tmpEval = CDbl(expression)
11001100 tmpEval = Atn(-tmpEval / Sqr(-tmpEval * tmpEval + 1 )) + 2 * Atn(1 )
11011101 If P_DEGREES Then
1102- tmpEval = tmpEval * 180 / PI
1102+ tmpEval = tmpEval * 180 / pi
11031103 End If
11041104 ArcCos = CStr(tmpEval)
11051105 Exit Function
@@ -1116,7 +1116,7 @@ Private Function ArcSin(ByRef expression As String, ByRef fName As String) As St
11161116 tmpEval = CDbl(expression)
11171117 tmpEval = Atn(tmpEval / Sqr(-tmpEval * tmpEval + 1 ))
11181118 If P_DEGREES Then
1119- tmpEval = tmpEval * 180 / PI
1119+ tmpEval = tmpEval * 180 / pi
11201120 End If
11211121 ArcSin = CStr(tmpEval)
11221122 Exit Function
@@ -1133,7 +1133,7 @@ Private Function ArcTan(ByRef expression As String, ByRef fName As String) As St
11331133 tmpEval = CDbl(expression)
11341134 tmpEval = Atn(tmpEval)
11351135 If P_DEGREES Then
1136- tmpEval = tmpEval * 180 / PI
1136+ tmpEval = tmpEval * 180 / pi
11371137 End If
11381138 ArcTan = CStr(tmpEval)
11391139 Exit Function
@@ -1660,10 +1660,10 @@ Private Function BETAINV_(p As Double, A As Double, B As Double) As Double
16601660 H = 2 / (1 / (2 * A - 1 ) + 1 / (2 * B - 1 ))
16611661 w = (x * Sqr(aL + H) / H) - (1 / (2 * B - 1 ) - 1 / (2 * A - 1 )) * _
16621662 (aL + 5 / 6 - 2 / (3 * H))
1663- x = A / (A + B * Exp (2 * w))
1663+ x = A / (A + B * exp (2 * w))
16641664 Else
16651665 lna = Log(A / (A + B)): lnb = Log(B / (A + B))
1666- t = Exp (A * lna) / A: u = Exp (B * lnb) / B
1666+ t = exp (A * lna) / A: u = exp (B * lnb) / B
16671667 w = t + u
16681668 If p < t / w Then
16691669 x = (A * w * p) ^ (1 / A)
@@ -1675,7 +1675,7 @@ Private Function BETAINV_(p As Double, A As Double, B As Double) As Double
16751675 Do While j < 10
16761676 If x = 0 Or x = 1 Then BETAINV_ = x: Exit Function
16771677 err = iBETA_(x, A, B) - p
1678- t = Exp (a1 * Log(x) + b1 * Log(1 - x) + afac)
1678+ t = exp (a1 * Log(x) + b1 * Log(1 - x) + afac)
16791679 u = err / t
16801680 t = u / (1 - 0.5 * MIN_(1 , u * (a1 / x - b1 / (1 - x))))
16811681 x = x - t
@@ -1743,7 +1743,7 @@ Private Function BETALN_(x As Double, y As Double) As Double
17431743End Function
17441744
17451745Private Function BETAPDF_ (x As Double , Alpha As Double , Beta As Double ) As Double
1746- BETAPDF_ = Exp ((Alpha - 1 ) * Log(x) + (Beta - 1 ) * Log(1 - x) - BETALN_(Alpha, Beta))
1746+ BETAPDF_ = exp ((Alpha - 1 ) * Log(x) + (Beta - 1 ) * Log(1 - x) - BETALN_(Alpha, Beta))
17471747End Function
17481748
17491749Private Function BETAPDF_EXCEL (x As Double , Alpha As Double , _
@@ -2015,9 +2015,9 @@ Private Function CHISQ_(x As Double, n As Double) As Double
20152015 CHISQ_ = 1 - q: Exit Function
20162016 End If
20172017 End If
2018- p = Exp (-0.5 * x)
2018+ p = exp (-0.5 * x)
20192019 If (REM_(n, 2 ) = 1 ) Then
2020- p = p * Sqr(2 * x / PI )
2020+ p = p * Sqr(2 * x / pi )
20212021 End If
20222022 k = n
20232023 Do While (k >= 2 )
@@ -2428,7 +2428,7 @@ Private Function Cosin(ByRef expression As String, ByRef fName As String) As Str
24282428 On Error GoTo err_Handler
24292429 tmpEval = CDbl(expression)
24302430 If P_DEGREES Then
2431- tmpEval = tmpEval * PI / 180
2431+ tmpEval = tmpEval * pi / 180
24322432 End If
24332433 Cosin = CStr(Cos(tmpEval))
24342434 Exit Function
@@ -3009,6 +3009,7 @@ Private Function EvalFunction(ByRef Argument As String, ByRef FunctionName As St
30093009 Case "aHour" : EvalFunction = Hour_(Argument, FunctionName)
30103010 Case "iBETA" : EvalFunction = iBETA(Argument, FunctionName)
30113011 Case "aIff" : EvalFunction = Iff_(Argument, FunctionName)
3012+ Case "aInstr" : EvalFunction = InStr_(Argument, FunctionName)
30123013 Case "InverseMatrix" : EvalFunction = InverseMatrix(Argument, FunctionName)
30133014 Case "aIPMT" : EvalFunction = IPMT_(Argument, FunctionName)
30143015 Case "aIRR" : EvalFunction = IRR_(Argument, FunctionName)
@@ -3128,7 +3129,7 @@ End Sub
31283129
31293130Private Function ExpEuler (ByRef expression As String , ByRef fName As String ) As String
31303131 On Error GoTo err_Handler
3131- ExpEuler = CStr(Exp (CDbl(expression)))
3132+ ExpEuler = CStr(exp (CDbl(expression)))
31323133 Exit Function
31333134err_Handler:
31343135 ExpEuler = e_ValueError
@@ -3166,7 +3167,7 @@ Private Function FACT(n As Double) As Double
31663167 pD = 0.577215664819072 + r * pC
31673168 r = 1 / (1 + r * pD)
31683169 If n > 0.5 Then
3169- r = (n * (1 - n) * PI ) / (r * Sin(PI * n))
3170+ r = (n * (1 - n) * pi ) / (r * Sin(pi * n))
31703171 End If
31713172 FACT = r
31723173End Function
@@ -3261,7 +3262,7 @@ Private Function FISHF_(F As Double, N1 As Double, N2 As Double) As Double
32613262 A = A + sth * cth * STATCOM(cth * cth, 2 , N2 - 3 , -1 ) / PID2
32623263 End If
32633264 If (N1 = 1 ) Then FISHF_ = 1 - A: Exit Function
3264- c = 4 * STATCOM(sth * sth, N2 + 1 , N1 + N2 - 4 , N2 - 2 ) * sth * (cth ^ N2) / PI
3265+ c = 4 * STATCOM(sth * sth, N2 + 1 , N1 + N2 - 4 , N2 - 2 ) * sth * (cth ^ N2) / pi
32653266 If (N2 = 1 ) Then FISHF_ = 1 - A + c / 2 : Exit Function
32663267 k = 2
32673268 Do While (k <= (N2 - 1 ) / 2 )
@@ -3318,7 +3319,7 @@ Private Function Fit(ByRef expression As String, ByRef fName As String) As Strin
33183319 Select Case fittingOption
33193320 Case 2 'Exponential [y = a*e^(b*x)]
33203321 solverCoeff(0 , 0 ) = 10 ^ solverCoeff(0 , 0 ) 'antilog_10 (A)
3321- solverCoeff(1 , 0 ) = solverCoeff(1 , 0 ) / Log10(Exp (1 )) 'B/log10(e)
3322+ solverCoeff(1 , 0 ) = solverCoeff(1 , 0 ) / Log10(exp (1 )) 'B/log10(e)
33223323 Case 3 'Exponential [y = a*b^x]
33233324 solverCoeff(0 , 0 ) = 10 ^ solverCoeff(0 , 0 ) 'antilog_10 (A)
33243325 solverCoeff(1 , 0 ) = 10 ^ solverCoeff(1 , 0 ) 'antilog_10 (B)
@@ -5085,10 +5086,10 @@ Private Function iBETAINV(p As Double, A As Double, B As Double) As Double
50855086 H = 2 / (1 / (2 * A - 1 ) + 1 / (2 * B - 1 ))
50865087 w = (x * Sqr(aL + H) / H) - (1 / (2 * B - 1 ) - 1 / (2 * A - 1 )) * _
50875088 (aL + 5 / 6 - 2 / (3 * H))
5088- x = A / (A + B * Exp (2 * w))
5089+ x = A / (A + B * exp (2 * w))
50895090 Else
50905091 lna = Log(A / (A + B)): lnb = Log(B / (A + B))
5091- t = Exp (A * lna) / A: u = Exp (B * lnb) / B
5092+ t = exp (A * lna) / A: u = exp (B * lnb) / B
50925093 w = t + u
50935094 If p < t / w Then
50945095 x = (A * w * p) ^ (1 / A)
@@ -5100,7 +5101,7 @@ Private Function iBETAINV(p As Double, A As Double, B As Double) As Double
51005101 Do While j < 10
51015102 If x = 0 Or x = 1 Then iBETAINV = x: Exit Function
51025103 err = iBETA_(x, A, B) - p
5103- t = Exp (a1 * Log(x) + b1 * Log(1 - x) + afac)
5104+ t = exp (a1 * Log(x) + b1 * Log(1 - x) + afac)
51045105 u = err / t
51055106 t = u / (1 - 0.5 * MIN_(1 , u * (a1 / x - b1 / (1 - x))))
51065107 x = x - t
@@ -5119,7 +5120,7 @@ Private Function iBETA_(x As Double, A As Double, B As Double) As Variant
51195120 If x = 0 Or x = 1 Then
51205121 BT = 0
51215122 Else
5122- BT = Exp (GAMMALN_(A + B) - GAMMALN_(A) - GAMMALN_(B) + A * Log(x) + B * Log(1 - x))
5123+ BT = exp (GAMMALN_(A + B) - GAMMALN_(A) - GAMMALN_(B) + A * Log(x) + B * Log(1 - x))
51235124 End If
51245125 If x < 0 Or x > 1 Then
51255126 iBETA_ = False : Exit Function
@@ -5166,6 +5167,52 @@ err_Handler:
51665167 d_lParenthesis & err.Description & d_rParenthesis
51675168End Function
51685169
5170+ Private Function InStr_ (ByRef expression As String , ByRef fName As String ) As String
5171+ Dim argsCount As Long
5172+ Dim tmpData() As String
5173+ Dim tmpEval As String
5174+ Dim LB As Long , UB As Long
5175+
5176+ On Error GoTo err_Handler
5177+ tmpData() = SplitArgs(expression)
5178+ LB = LBound(tmpData)
5179+ UB = UBound(tmpData)
5180+ argsCount = UB - LB + 1
5181+ Select Case argsCount
5182+ Case 2
5183+ tmpEval = CStr(InStr( _
5184+ 1 , _
5185+ FormatLiteralString(tmpData(LB), True ), _
5186+ FormatLiteralString(tmpData(UB), True ) _
5187+ ) _
5188+ )
5189+ Case 3
5190+ tmpEval = CStr(InStr( _
5191+ CLng(tmpData(LB)), _
5192+ FormatLiteralString(tmpData(LB + 1 ), True ), _
5193+ FormatLiteralString(tmpData(UB), True ) _
5194+ ) _
5195+ )
5196+ Case 4
5197+ tmpEval = CStr(InStr( _
5198+ CLng(tmpData(LB)), _
5199+ FormatLiteralString(tmpData(LB + 1 ), True ), _
5200+ FormatLiteralString(tmpData(LB + 2 ), True ), _
5201+ CLng(tmpData(UB)) _
5202+ ) _
5203+ )
5204+ Case Else
5205+ InStr_ = e_ValueError
5206+ Exit Function
5207+ End Select
5208+ InStr_ = tmpEval
5209+ Exit Function
5210+ err_Handler:
5211+ InStr_ = e_ValueError
5212+ BuildErrMessage errEvalError, d_lCurly & fName & d_rCurly & " | Error#: " & err.Number & d_Space & _
5213+ d_lParenthesis & err.Description & d_rParenthesis
5214+ End Function
5215+
51695216Private Function ImplicitMultFlag (ByRef Char As String ) As Boolean
51705217 If LenB(Char) Then
51715218 Select Case AscW(Char)
@@ -6990,7 +7037,7 @@ Private Function NORM_(z As Double) As Double
69907037 Dim q As Double
69917038 q = z * z
69927039 If (Abs(z) > 7 ) Then
6993- NORM_ = (1 - 1 / q + 3 / (q * q)) * Exp (-q / 2 ) / (Abs(z) * Sqr(PID2))
7040+ NORM_ = (1 - 1 / q + 3 / (q * q)) * exp (-q / 2 ) / (Abs(z) * Sqr(PID2))
69947041 Else
69957042 NORM_ = CHISQ_(q, 1 )
69967043 End If
@@ -8191,7 +8238,7 @@ Private Function Sine(ByRef expression As String, ByRef fName As String) As Stri
81918238 On Error GoTo err_Handler
81928239 tmpEval = CDbl(expression)
81938240 If P_DEGREES Then
8194- tmpEval = tmpEval * PI / 180
8241+ tmpEval = tmpEval * pi / 180
81958242 End If
81968243 Sine = CStr(Sin(tmpEval))
81978244 Exit Function
@@ -8685,7 +8732,7 @@ Private Function Tangent(ByRef expression As String, ByRef fName As String) As S
86858732 On Error GoTo err_Handler
86868733 tmpEval = CDbl(expression)
86878734 If P_DEGREES Then
8688- tmpEval = tmpEval * PI / 180
8735+ tmpEval = tmpEval * pi / 180
86898736 End If
86908737 Tangent = CStr(Tan(tmpEval))
86918738 Exit Function
0 commit comments