Skip to content

Commit c2b8b2c

Browse files
committed
Added ForceBoolean property
Allows to ignore evaluation errors and get False as the result of the evaluation. This can be useful when evaluating piecewise functions.
1 parent c33b90c commit c2b8b2c

File tree

1 file changed

+32
-0
lines changed

1 file changed

+32
-0
lines changed

src/VBAexpressions.cls

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -166,6 +166,7 @@ Private P_DEGREES As Boolean
166166
Private P_ERRORDESC As String
167167
Private P_ERRTYPE As ExpressionErrors
168168
Private P_EXPRESSION As String
169+
Private P_FORCE_BOOLEAN As Boolean
169170
Private P_FORMATRESULT As Boolean
170171
Private P_GALLOPING_MODE As Boolean
171172
Private P_RESULT As Variant
@@ -283,6 +284,7 @@ Private Sub Class_Initialize()
283284
FunctionsId() = Split(BuildinFunctIDList, ";")
284285
FunctionsName() = Split(BuildinFunctNameList, ";")
285286
Set P_SCOPE = New VBAexpressionsScope
287+
P_FORCE_BOOLEAN = False
286288
InitCBbuffer UserDefFunctions
287289
'@--------------------------------------------------------------------
288290
' Populate linked index constructor
@@ -370,6 +372,18 @@ Public Property Get expression() As String
370372
expression = P_EXPRESSION
371373
End Property
372374

375+
''' <summary>
376+
''' When True, a False is returned on evaluation errors.
377+
''' This can be useful when evaluating piecewise functions.
378+
''' </summary>
379+
Public Property Let ForceBoolean(aValue As Boolean)
380+
P_FORCE_BOOLEAN = aValue
381+
End Property
382+
383+
Public Property Get ForceBoolean() As Boolean
384+
ForceBoolean = P_FORCE_BOOLEAN
385+
End Property
386+
373387
''' <summary>
374388
''' Indicates if the results will be converted to standard VBA strings
375389
''' </summary>
@@ -722,6 +736,7 @@ Private Function average(ByRef expression As String) As Double
722736
End Function
723737

724738
Private Sub BottomLevelEval(ByRef aToken As token)
739+
On Error GoTo BLevelEval_errHanlder
725740
If aToken.OperationToken < 100 Then 'Arithmetic operators
726741
Select Case aToken.OperationToken
727742
Case OperatorToken.otSum
@@ -806,6 +821,14 @@ Private Sub BottomLevelEval(ByRef aToken As token)
806821
End Select
807822
End If
808823
End If
824+
Exit Sub
825+
BLevelEval_errHanlder:
826+
If Not P_FORCE_BOOLEAN Then
827+
aToken.EvalResult = e_ValueError
828+
Else
829+
aToken.EvalResult = False
830+
End If
831+
P_ERRTYPE = errEvalError
809832
End Sub
810833

811834
Private Sub BuildErrMessage(ErrorType As ExpressionErrors, Optional AditionalContext As String)
@@ -1230,6 +1253,7 @@ Eval_errHandler:
12301253
End Function
12311254

12321255
Private Function EvalFunction(ByRef Argument As String, ByRef FunctionName As String, Optional IsUDF As Boolean = False) As String
1256+
On Error GoTo EvalFunction_errHandler
12331257
If Not IsUDF Then
12341258
Select Case FunctionName
12351259
Case "Absolute"
@@ -1384,6 +1408,14 @@ Private Function EvalFunction(ByRef Argument As String, ByRef FunctionName As St
13841408
Else
13851409
EvalFunction = EvalUDF(FunctionName, Argument)
13861410
End If
1411+
Exit Function
1412+
EvalFunction_errHandler:
1413+
If Not P_FORCE_BOOLEAN Then
1414+
EvalFunction = e_ValueError
1415+
Else
1416+
EvalFunction = False
1417+
End If
1418+
P_ERRTYPE = errEvalError
13871419
End Function
13881420

13891421
Private Function EvalUDF(ByRef UDFname As String, ByRef expression As String) As String

0 commit comments

Comments
 (0)