@@ -119,7 +119,7 @@ Option Base 0
119
119
'
120
120
'///////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
121
121
' CONSTANTS:
122
- Private PI As Double
122
+ Private pi As Double
123
123
Private PID2 As Double
124
124
Private e As Double
125
125
Private Const op_plus As String = "+"
@@ -306,9 +306,9 @@ End Type
306
306
''' </summary>
307
307
Private Sub Class_Initialize ()
308
308
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 )
312
312
P_SEPARATORCHAR = d_Semicolon
313
313
P_DEC_SYMBOL = dsDot
314
314
AscDecSymbol = 46
@@ -317,7 +317,7 @@ Private Sub Class_Initialize()
317
317
BuildinFunctIDList = "abs;floor;achisq;asin;acos;aerf;afishf;agauss;asc;anorm;atn;astudt;array;avg;beta.dist" & _
318
318
";betainv;ceil;chisq;cholesky;cholinverse;cholsolve;chr;cos;choose;date;dateadd;datediff" & _
319
319
";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" & _
321
321
";ln;lsqrsolve;ludecomp;lusolve;max;mid;min;minute;mirr;mlr;mmult;mneg;mround" & _
322
322
";msum;mtranspose;month;monthname;norm;now;nper;npv;percent;pmt;ppmt;pow;pv" & _
323
323
";qr;rate;rem;replace;right;round;sgn;sin;sln;solve;sqr;sqrt;sum;studt;switch" & _
@@ -327,7 +327,7 @@ Private Sub Class_Initialize()
327
327
";ASTUDT;strArray;Average;Beta_Distribution;BETAINV;aCeiling;CHISQ;CholeskyDec;CholeskyInverseMatrix" & _
328
328
";CholeskySolve;ASCIIchr;Cosin;aChoose;aDate;aDateAdd;aDateDiff;aDatePart;aDateSerial" & _
329
329
";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" & _
331
331
";aIPMT;aIRR;LowerCase;aLeft;aLen;Logarithm;LgN;LN;LSQRsolve;LUdecomposition" & _
332
332
";LUSolveLinearSystem;Max;Middle;Min;aMinute;aMIRR;MultiLinearReg;MatrixMult" & _
333
333
";MatrixNegation;MatrixRound;MatrixSum;MatrixTranspose;aMonth;aMonthName;NORM" & _
@@ -1099,7 +1099,7 @@ Private Function ArcCos(ByRef expression As String, ByRef fName As String) As St
1099
1099
tmpEval = CDbl(expression)
1100
1100
tmpEval = Atn(-tmpEval / Sqr(-tmpEval * tmpEval + 1 )) + 2 * Atn(1 )
1101
1101
If P_DEGREES Then
1102
- tmpEval = tmpEval * 180 / PI
1102
+ tmpEval = tmpEval * 180 / pi
1103
1103
End If
1104
1104
ArcCos = CStr(tmpEval)
1105
1105
Exit Function
@@ -1116,7 +1116,7 @@ Private Function ArcSin(ByRef expression As String, ByRef fName As String) As St
1116
1116
tmpEval = CDbl(expression)
1117
1117
tmpEval = Atn(tmpEval / Sqr(-tmpEval * tmpEval + 1 ))
1118
1118
If P_DEGREES Then
1119
- tmpEval = tmpEval * 180 / PI
1119
+ tmpEval = tmpEval * 180 / pi
1120
1120
End If
1121
1121
ArcSin = CStr(tmpEval)
1122
1122
Exit Function
@@ -1133,7 +1133,7 @@ Private Function ArcTan(ByRef expression As String, ByRef fName As String) As St
1133
1133
tmpEval = CDbl(expression)
1134
1134
tmpEval = Atn(tmpEval)
1135
1135
If P_DEGREES Then
1136
- tmpEval = tmpEval * 180 / PI
1136
+ tmpEval = tmpEval * 180 / pi
1137
1137
End If
1138
1138
ArcTan = CStr(tmpEval)
1139
1139
Exit Function
@@ -1660,10 +1660,10 @@ Private Function BETAINV_(p As Double, A As Double, B As Double) As Double
1660
1660
H = 2 / (1 / (2 * A - 1 ) + 1 / (2 * B - 1 ))
1661
1661
w = (x * Sqr(aL + H) / H) - (1 / (2 * B - 1 ) - 1 / (2 * A - 1 )) * _
1662
1662
(aL + 5 / 6 - 2 / (3 * H))
1663
- x = A / (A + B * Exp (2 * w))
1663
+ x = A / (A + B * exp (2 * w))
1664
1664
Else
1665
1665
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
1667
1667
w = t + u
1668
1668
If p < t / w Then
1669
1669
x = (A * w * p) ^ (1 / A)
@@ -1675,7 +1675,7 @@ Private Function BETAINV_(p As Double, A As Double, B As Double) As Double
1675
1675
Do While j < 10
1676
1676
If x = 0 Or x = 1 Then BETAINV_ = x: Exit Function
1677
1677
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)
1679
1679
u = err / t
1680
1680
t = u / (1 - 0.5 * MIN_(1 , u * (a1 / x - b1 / (1 - x))))
1681
1681
x = x - t
@@ -1743,7 +1743,7 @@ Private Function BETALN_(x As Double, y As Double) As Double
1743
1743
End Function
1744
1744
1745
1745
Private 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))
1747
1747
End Function
1748
1748
1749
1749
Private Function BETAPDF_EXCEL (x As Double , Alpha As Double , _
@@ -2015,9 +2015,9 @@ Private Function CHISQ_(x As Double, n As Double) As Double
2015
2015
CHISQ_ = 1 - q: Exit Function
2016
2016
End If
2017
2017
End If
2018
- p = Exp (-0.5 * x)
2018
+ p = exp (-0.5 * x)
2019
2019
If (REM_(n, 2 ) = 1 ) Then
2020
- p = p * Sqr(2 * x / PI )
2020
+ p = p * Sqr(2 * x / pi )
2021
2021
End If
2022
2022
k = n
2023
2023
Do While (k >= 2 )
@@ -2428,7 +2428,7 @@ Private Function Cosin(ByRef expression As String, ByRef fName As String) As Str
2428
2428
On Error GoTo err_Handler
2429
2429
tmpEval = CDbl(expression)
2430
2430
If P_DEGREES Then
2431
- tmpEval = tmpEval * PI / 180
2431
+ tmpEval = tmpEval * pi / 180
2432
2432
End If
2433
2433
Cosin = CStr(Cos(tmpEval))
2434
2434
Exit Function
@@ -3009,6 +3009,7 @@ Private Function EvalFunction(ByRef Argument As String, ByRef FunctionName As St
3009
3009
Case "aHour" : EvalFunction = Hour_(Argument, FunctionName)
3010
3010
Case "iBETA" : EvalFunction = iBETA(Argument, FunctionName)
3011
3011
Case "aIff" : EvalFunction = Iff_(Argument, FunctionName)
3012
+ Case "aInstr" : EvalFunction = InStr_(Argument, FunctionName)
3012
3013
Case "InverseMatrix" : EvalFunction = InverseMatrix(Argument, FunctionName)
3013
3014
Case "aIPMT" : EvalFunction = IPMT_(Argument, FunctionName)
3014
3015
Case "aIRR" : EvalFunction = IRR_(Argument, FunctionName)
@@ -3128,7 +3129,7 @@ End Sub
3128
3129
3129
3130
Private Function ExpEuler (ByRef expression As String , ByRef fName As String ) As String
3130
3131
On Error GoTo err_Handler
3131
- ExpEuler = CStr(Exp (CDbl(expression)))
3132
+ ExpEuler = CStr(exp (CDbl(expression)))
3132
3133
Exit Function
3133
3134
err_Handler:
3134
3135
ExpEuler = e_ValueError
@@ -3166,7 +3167,7 @@ Private Function FACT(n As Double) As Double
3166
3167
pD = 0.577215664819072 + r * pC
3167
3168
r = 1 / (1 + r * pD)
3168
3169
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))
3170
3171
End If
3171
3172
FACT = r
3172
3173
End Function
@@ -3261,7 +3262,7 @@ Private Function FISHF_(F As Double, N1 As Double, N2 As Double) As Double
3261
3262
A = A + sth * cth * STATCOM(cth * cth, 2 , N2 - 3 , -1 ) / PID2
3262
3263
End If
3263
3264
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
3265
3266
If (N2 = 1 ) Then FISHF_ = 1 - A + c / 2 : Exit Function
3266
3267
k = 2
3267
3268
Do While (k <= (N2 - 1 ) / 2 )
@@ -3318,7 +3319,7 @@ Private Function Fit(ByRef expression As String, ByRef fName As String) As Strin
3318
3319
Select Case fittingOption
3319
3320
Case 2 'Exponential [y = a*e^(b*x)]
3320
3321
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)
3322
3323
Case 3 'Exponential [y = a*b^x]
3323
3324
solverCoeff(0 , 0 ) = 10 ^ solverCoeff(0 , 0 ) 'antilog_10 (A)
3324
3325
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
5085
5086
H = 2 / (1 / (2 * A - 1 ) + 1 / (2 * B - 1 ))
5086
5087
w = (x * Sqr(aL + H) / H) - (1 / (2 * B - 1 ) - 1 / (2 * A - 1 )) * _
5087
5088
(aL + 5 / 6 - 2 / (3 * H))
5088
- x = A / (A + B * Exp (2 * w))
5089
+ x = A / (A + B * exp (2 * w))
5089
5090
Else
5090
5091
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
5092
5093
w = t + u
5093
5094
If p < t / w Then
5094
5095
x = (A * w * p) ^ (1 / A)
@@ -5100,7 +5101,7 @@ Private Function iBETAINV(p As Double, A As Double, B As Double) As Double
5100
5101
Do While j < 10
5101
5102
If x = 0 Or x = 1 Then iBETAINV = x: Exit Function
5102
5103
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)
5104
5105
u = err / t
5105
5106
t = u / (1 - 0.5 * MIN_(1 , u * (a1 / x - b1 / (1 - x))))
5106
5107
x = x - t
@@ -5119,7 +5120,7 @@ Private Function iBETA_(x As Double, A As Double, B As Double) As Variant
5119
5120
If x = 0 Or x = 1 Then
5120
5121
BT = 0
5121
5122
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))
5123
5124
End If
5124
5125
If x < 0 Or x > 1 Then
5125
5126
iBETA_ = False : Exit Function
@@ -5166,6 +5167,52 @@ err_Handler:
5166
5167
d_lParenthesis & err.Description & d_rParenthesis
5167
5168
End Function
5168
5169
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
+
5169
5216
Private Function ImplicitMultFlag (ByRef Char As String ) As Boolean
5170
5217
If LenB(Char) Then
5171
5218
Select Case AscW(Char)
@@ -6990,7 +7037,7 @@ Private Function NORM_(z As Double) As Double
6990
7037
Dim q As Double
6991
7038
q = z * z
6992
7039
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))
6994
7041
Else
6995
7042
NORM_ = CHISQ_(q, 1 )
6996
7043
End If
@@ -8191,7 +8238,7 @@ Private Function Sine(ByRef expression As String, ByRef fName As String) As Stri
8191
8238
On Error GoTo err_Handler
8192
8239
tmpEval = CDbl(expression)
8193
8240
If P_DEGREES Then
8194
- tmpEval = tmpEval * PI / 180
8241
+ tmpEval = tmpEval * pi / 180
8195
8242
End If
8196
8243
Sine = CStr(Sin(tmpEval))
8197
8244
Exit Function
@@ -8685,7 +8732,7 @@ Private Function Tangent(ByRef expression As String, ByRef fName As String) As S
8685
8732
On Error GoTo err_Handler
8686
8733
tmpEval = CDbl(expression)
8687
8734
If P_DEGREES Then
8688
- tmpEval = tmpEval * PI / 180
8735
+ tmpEval = tmpEval * pi / 180
8689
8736
End If
8690
8737
Tangent = CStr(Tan(tmpEval))
8691
8738
Exit Function
0 commit comments