@@ -156,6 +156,7 @@ Private Const Tiny As Double = 1E-20
156156'#
157157'///////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
158158' VARIABLES:
159+ Private AscDecSymbol As Long
159160Private AssignedExpression As Boolean
160161Private BuildinFunctIDList As String
161162Private BuildinFunctNameList As String
@@ -167,6 +168,7 @@ Private FunctionsName() As String
167168Private GeneratedTree As Boolean
168169Private IsUDFFunction As Boolean
169170Private LIndexConstruc(0 To 2 ) As String
171+ Private P_DEC_SYMBOL As DecimalSymbol
170172Private P_DEGREES As Boolean
171173Private P_ERRORDESC As String
172174Private P_ERRTYPE As ExpressionErrors
@@ -233,6 +235,10 @@ Public Enum ExpressionErrors
233235 errVariableNotAssigned = 4
234236 errMissingArgsOrTooManyArgs = 5
235237End Enum
238+ Public Enum DecimalSymbol
239+ dsDot = 0
240+ dsComma = 1
241+ End Enum
236242'///////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
237243'#
238244'///////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
@@ -297,6 +303,8 @@ Private Sub Class_Initialize()
297303 PID2 = pi / 2
298304 e = Exp(1 )
299305 P_SEPARATORCHAR = ";"
306+ P_DEC_SYMBOL = dsDot
307+ AscDecSymbol = 46
300308 P_GALLOPING_MODE = True
301309 P_FORMATRESULT = False
302310 BuildinFunctIDList = "abs;floor;achisq;asin;acos;aerf;afishf;agauss;asc;anorm;atn;astudt;array;avg" & _
@@ -367,6 +375,38 @@ Public Property Get CurrentVarValues() As String
367375 CurrentVarValues = P_SCOPE.CurrentVarValues
368376End Property
369377
378+ ''' <summary>
379+ ''' Gets or sets the decimal symbol. The allowed options are
380+ ''' the dot or comma, if another character is specified
381+ ''' dot will be used which is the default value.
382+ ''' </summary>
383+ Public Property Get DecimalSymbol() As String
384+ Select Case P_DEC_SYMBOL
385+ Case 0
386+ DecimalSymbol = "."
387+ Case 1
388+ DecimalSymbol = ","
389+ End Select
390+ End Property
391+
392+ Public Property Let DecimalSymbol(aValue As String )
393+ If LenB(aValue) > 2 Then
394+ P_DEC_SYMBOL = 0
395+ Else
396+ Dim tmpLng As Long
397+
398+ tmpLng = AscW(aValue)
399+ If tmpLng = 44 Or tmpLng = 46 Then
400+ AscDecSymbol = tmpLng
401+ If tmpLng = 46 Then
402+ P_DEC_SYMBOL = 0
403+ Else
404+ P_DEC_SYMBOL = 1
405+ End If
406+ End If
407+ End If
408+ End Property
409+
370410''' <summary>
371411''' Gets or sets the behaviour when calculating trigonometric functions. If True, the program
372412''' will assume argument passed in degrees for all trigonometric functions.
@@ -492,7 +532,13 @@ Public Property Get SeparatorChar() As String
492532End Property
493533
494534Public Property Let SeparatorChar(aValue As String )
495- P_SEPARATORCHAR = aValue
535+ If LenB(aValue) = 2 Then
536+ Select Case AscW(aValue)
537+ Case 44 , 46 'Reject reserved decimal symbols
538+ Case Else
539+ P_SEPARATORCHAR = aValue
540+ End Select
541+ End If
496542End Property
497543
498544''' <summary>
@@ -1646,7 +1692,7 @@ Private Function CastOPtype(ByRef strOperand As String, ByRef Negate As Boolean)
16461692 Dim OpAscw As Long
16471693 OpAscw = AscW(strOperand)
16481694 Select Case OpAscw
1649- Case 48 To 57 , 43 , 45 , 46
1695+ Case 48 To 57 , 43 , 45 , AscDecSymbol
16501696 CastOPtype = CDbl(strOperand)
16511697 Case Else
16521698 If IsLiteralString(strOperand) Then 'Literal strings like ['string']
@@ -4741,7 +4787,7 @@ Private Sub GetTokenStart(ByRef expression As String, ByRef startIndex As Long,
47414787 Do While (InStrB(1 , op_AllItems, curChar) = 0 ) And outLng > 1
47424788 outLng = outLng - 2
47434789 curChar = MidB$(expression, outLng, 2 )
4744- If AscW(curChar) = 46 Then 'Dot "."
4790+ If AscW(curChar) = AscDecSymbol Then 'Decimal symbol: [.][,]
47454791 outLng = outLng - 2
47464792 If outLng > 0 Then
47474793 curChar = MidB$(expression, outLng, 2 )
@@ -5012,7 +5058,7 @@ End Function
50125058Private Function ImplicitMultFlag (ByRef Char As String ) As Boolean
50135059 If LenB(Char) Then
50145060 Select Case AscW(Char)
5015- Case 46 , 48 To 57
5061+ Case AscDecSymbol , 48 To 57
50165062 ImplicitMultFlag = True
50175063 Case Else
50185064 ImplicitMultFlag = False
@@ -5255,7 +5301,7 @@ End Function
52555301Private Function IsExtAlphaNumeric (ByRef Char As String ) As Boolean
52565302 If LenB(Char) Then
52575303 Select Case AscW(Char)
5258- Case 46 , 48 To 57 , 65 To 90 , 95 , 97 To 122
5304+ Case AscDecSymbol , 48 To 57 , 65 To 90 , 95 , 97 To 122
52595305 IsExtAlphaNumeric = True
52605306 Case Else
52615307 IsExtAlphaNumeric = False
0 commit comments