@@ -28,6 +28,7 @@ Private Const CHR_APOSTROPHE As String = "'"
2828Private Const CHR_BACKSLASH As String = "\"
2929Private Const CHR_DOUBLE_QUOTES As String = """"
3030Private Const CHR_TILDE As String = "~"
31+ Private Const CHR_CARET As String = "^"
3132'////////////////////////////////////////////////////////////////////////////////////////////
3233'#
3334'////////////////////////////////////////////////////////////////////////////////////////////
@@ -3152,17 +3153,19 @@ Private Function SniffInString(ByRef confObject As CSVparserConfig, _
31523153 For j = LBound(LinesEnds) To UBound(LinesEnds)
31533154 If InStrB(1 , TmpCSVstr, LinesEnds(j)) Then
31543155 For k = LBound(QuoteChar) To UBound(QuoteChar)
3156+ '@--------------------------------------------------------------------------------
3157+ 'Set CSV dialect
3158+ .dialect.fieldsDelimiter = TmpDelimiters(i)
3159+ .dialect.recordsDelimiter = LinesEnds(j)
3160+ .dialect.quoteToken = QuoteChar(k)
3161+ Set ImportedTable = New CSVArrayList
3162+ ParseCSVstring TmpCSVstr, tmpConfig, ImportedTable, EmptyParam
3163+ '@--------------------------------------------------------------------------------
3164+ 'Save results with keys
31553165 If InStrB(1 , TmpCSVstr, GetQuoteChar(QuoteChar(k))) Then
3156- '@--------------------------------------------------------------------------------
3157- 'Set CSV dialect
3158- .dialect.fieldsDelimiter = TmpDelimiters(i)
3159- .dialect.recordsDelimiter = LinesEnds(j)
3160- .dialect.quoteToken = QuoteChar(k)
3161- Set ImportedTable = New CSVArrayList
3162- ParseCSVstring TmpCSVstr, tmpConfig, ImportedTable, EmptyParam
3163- '@--------------------------------------------------------------------------------
3164- 'Save results with keys
31653166 ScoreArray.AddIndexedItem DialectToString(.dialect), GuesserHelper.TableScore(ImportedTable)
3167+ Else
3168+ ScoreArray.AddIndexedItem DialectToString(.dialect) & CHR_CARET, GuesserHelper.TableScore(ImportedTable) / 2
31663169 End If
31673170 Next k
31683171 End If
@@ -3209,7 +3212,11 @@ Private Function StringToDialect(ByRef dialectString As String) As CSVdialect
32093212 With tmpResult
32103213 .fieldsDelimiter = tmpArr(idx)
32113214 .recordsDelimiter = tmpArr(idx + 1 )
3212- .quoteToken = GetQuoteToken(CLng(tmpArr(idx + 2 )))
3215+ If InStrB(1 , dialectString, CHR_CARET) Then
3216+ .quoteToken = QuoteTokens.DoubleQuotes
3217+ Else
3218+ .quoteToken = GetQuoteToken(CLng(tmpArr(idx + 2 )))
3219+ End If
32133220 End With
32143221 Set StringToDialect = tmpResult
32153222End Function
0 commit comments