@@ -1267,21 +1267,23 @@ Private Sub GuessInString(ByRef confObject As parserConfig, _
12671267 ByRef CSVstring As String , _
12681268 Optional Buffered As Boolean = False )
12691269
1270- Dim tmpCSVstr As String
1271- Dim UBlinesEnds() As Long
1272- Dim LinesEnds() As String
1270+ Dim CtableScore() As Double
12731271 Dim delIdx As Long
1274- Dim tmpDelimiters() As String
1275- Dim guessResults As ECPArrayList
12761272 Dim emptyParam() As Variant
1277- Dim StartRec As Long
12781273 Dim EndRec As Long
1279- Dim CtableScore() As Double
1280- Dim QuoteChar() As EscapeTokens
1274+ Dim guessResults As ECPArrayList
12811275 Dim L0_FieldDelimiter As Long
12821276 Dim L1_FieldDelimiter As Long
1283- Dim UBquoteChar () As Long
1277+ Dim LinesEnds () As String
12841278 Dim Quote As String
1279+ Dim QuoteChar() As EscapeTokens
1280+ Dim skipEmpty As Boolean
1281+ Dim skipComments As Boolean
1282+ Dim StartRec As Long
1283+ Dim tmpCSVstr As String
1284+ Dim tmpDelimiters() As String
1285+ Dim UBlinesEnds() As Long
1286+ Dim UBquoteChar() As Long
12851287
12861288 ReDim LinesEnds(0 To 2 )
12871289 '@--------------------------------------------------------------------------------
@@ -1339,8 +1341,12 @@ Private Sub GuessInString(ByRef confObject As parserConfig, _
13391341 'Guess fields delimiter using 10 samples lines
13401342 StartRec = .startingRecord
13411343 EndRec = .endingRecord
1344+ skipComments = .skipCommentLines
1345+ skipEmpty = .skipEmptyLines
13421346 .startingRecord = 1
13431347 .endingRecord = 10
1348+ .skipCommentLines = True
1349+ .skipEmptyLines = True
13441350 For delIdx = LBound(tmpDelimiters) To UBound(tmpDelimiters)
13451351 If InStrB(1 , CSVstring, tmpDelimiters(delIdx)) Then
13461352 .fieldsDelimiter = tmpDelimiters(delIdx)
@@ -1349,10 +1355,10 @@ Private Sub GuessInString(ByRef confObject As parserConfig, _
13491355 If Not guessResults Is Nothing Then
13501356 CtableScore(delIdx) = TableScore(guessResults)
13511357 Else
1352- CtableScore(delIdx) = 1.6 E+ 308
1358+ CtableScore(delIdx) = 1 E+ 30
13531359 End If
13541360 Else
1355- CtableScore(delIdx) = 1.6 E+ 308
1361+ CtableScore(delIdx) = 1 E+ 30
13561362 End If
13571363 Next delIdx
13581364 '@--------------------------------------------------------------------------------
@@ -1361,6 +1367,8 @@ Private Sub GuessInString(ByRef confObject As parserConfig, _
13611367 .fieldsDelimiter = tmpDelimiters(L1_FieldDelimiter)
13621368 .startingRecord = StartRec
13631369 .endingRecord = EndRec
1370+ .skipCommentLines = skipComments
1371+ .skipEmptyLines = skipEmpty
13641372 End With
13651373 Erase emptyParam
13661374 Erase CtableScore
@@ -2425,15 +2433,19 @@ Private Function RecordScore(ByRef strArray As Variant) As Double
24252433 Dim CumulativeScore As Double
24262434
24272435 On Error GoTo RecordScore_ErrHandler
2428- CfieldScore = FieldScore(strArray)
2429- CumulativeScore = 0
2430- For L0 = LBound(strArray) To UBound(strArray)
2431- CumulativeScore = CumulativeScore + (LenB(strArray(L0)) - CfieldScore) ^ 2
2432- Next L0
2433- RecordScore = (CumulativeScore / (UBound(strArray) - LBound(strArray))) ^ 0.5
2436+ If UBound(strArray) Then
2437+ CfieldScore = FieldScore(strArray)
2438+ CumulativeScore = 0
2439+ For L0 = LBound(strArray) To UBound(strArray)
2440+ CumulativeScore = CumulativeScore + (LenB(strArray(L0)) - CfieldScore) ^ 2
2441+ Next L0
2442+ RecordScore = (CumulativeScore / (UBound(strArray) - LBound(strArray))) ^ 0.5
2443+ Else
2444+ RecordScore = LenB(strArray(UBound(strArray)))
2445+ End If
24342446 Exit Function
24352447RecordScore_ErrHandler:
2436- RecordScore = 1.6 E+ 308
2448+ RecordScore = 1 E+ 30
24372449End Function
24382450Private Function RequestedField (ByVal FieldIndex As Long , _
24392451 ByVal mxReq As Long ) As Boolean
@@ -2488,7 +2500,7 @@ Private Sub SkipUnwantedLines(ByRef idx As Long, _
24882500 ByRef MaxIdx As Long , _
24892501 ByRef arr() As String , _
24902502 ByVal CommentToken As Long , _
2491- Optional SkipComments As Boolean = True , _
2503+ Optional skipComments As Boolean = True , _
24922504 Optional skipEmptyLines As Boolean = True )
24932505 Dim CurLength As Long
24942506 Dim CharCode As Long
@@ -2507,7 +2519,7 @@ Private Sub SkipUnwantedLines(ByRef idx As Long, _
25072519 Else
25082520 CharCode = AscW(arr(idx))
25092521 If CharCode = CommentToken Then 'Commented line found
2510- If SkipComments Then
2522+ If skipComments Then
25112523 UnwantedLine = True
25122524 End If
25132525 End If
@@ -3050,7 +3062,7 @@ Private Sub StreamSkipUnwantedLines(ByRef idx As Long, _
30503062 ByRef recDelimiter As String , _
30513063 ByVal CommentToken As Long , _
30523064 ByRef QuotedStreamVariable As Boolean , _
3053- Optional SkipComments As Boolean = True , _
3065+ Optional skipComments As Boolean = True , _
30543066 Optional skipEmptyLines As Boolean = True )
30553067 Dim CurLength As Long
30563068 Dim CharCode As Long
@@ -3070,7 +3082,7 @@ start:
30703082 Else
30713083 CharCode = AscW(arr(idx))
30723084 If CharCode = CommentToken Then 'Commented line found
3073- If SkipComments Then
3085+ If skipComments Then
30743086 UnwantedLine = True
30753087 End If
30763088 End If
@@ -3239,4 +3251,5 @@ Private Function UnixToStandardEscapeSeq(ByRef UnixEscapedString As String, _
32393251 Else
32403252 UnixToStandardEscapeSeq = UnixEscapedString
32413253 End If
3242- End Function
3254+ End Function
3255+
0 commit comments