@@ -210,45 +210,6 @@ Private Sub Class_Terminate()
210210 Set P_CSV_DATA = Nothing
211211 Set P_CSV_HEADER = Nothing
212212End Sub
213- Private Function ArrayListAVGStdDev (ByRef ArrayList As ECPArrayList ) As Double
214- Dim L0 As Long
215- Dim StdDevSUM As Double
216-
217- StdDevSUM = 0
218- For L0 = 0 To ArrayList.count - 1
219- StdDevSUM = StdDevSUM + ArrayStrStdDev(ArrayList(L0))
220- Next L0
221- ArrayListAVGStdDev = StdDevSUM / ArrayList.count
222- End Function
223- Private Function ArrayStrLenAVG (ByRef strArray As Variant ) As Double
224- Dim L0 As Long
225- Dim tmpSUM As Double
226-
227- tmpSUM = 0
228- For L0 = LBound(strArray) To UBound(strArray)
229- tmpSUM = tmpSUM + LenB(strArray(L0))
230- Next L0
231- ArrayStrLenAVG = tmpSUM / (1 + UBound(strArray) - LBound(strArray))
232- End Function
233- Private Function ArrayStrStdDev (ByRef strArray As Variant ) As Double
234- Dim arrLB As Long
235- Dim arrUB As Long
236- Dim L0 As Long
237- Dim LengthsAVG As Double
238- Dim CumulativeAVGsquaredDiff As Double
239- Dim LengthsSum As Double
240-
241- On Error GoTo ArrStrStdDev_ErrHandler
242- LengthsAVG = ArrayStrLenAVG(strArray)
243- CumulativeAVGsquaredDiff = 0
244- For L0 = LBound(strArray) To UBound(strArray)
245- CumulativeAVGsquaredDiff = CumulativeAVGsquaredDiff + (LenB(strArray(L0)) - LengthsAVG) ^ 2
246- Next L0
247- ArrayStrStdDev = (CumulativeAVGsquaredDiff / (UBound(strArray) - LBound(strArray))) ^ 0.5
248- Exit Function
249- ArrStrStdDev_ErrHandler:
250- ArrayStrStdDev = 1.6 E+308
251- End Function
252213Public Sub ClearData ()
253214 Set P_CSV_DATA = New ECPArrayList
254215 Set P_CSV_HEADER = New ECPArrayList
@@ -661,6 +622,16 @@ ErrHandler_ExportToCSV:
661622 P_SUCCESSFUL_EXPORT = False
662623 P_ERROR_DESC = "[CSV file Export]: " & P_ERROR_DESC
663624End Sub
625+ Private Function FieldScore (ByRef strArray As Variant ) As Double
626+ Dim L0 As Long
627+ Dim tmpSUM As Double
628+
629+ tmpSUM = 0
630+ For L0 = LBound(strArray) To UBound(strArray)
631+ tmpSUM = tmpSUM + LenB(strArray(L0))
632+ Next L0
633+ FieldScore = tmpSUM / (1 + UBound(strArray) - LBound(strArray))
634+ End Function
664635Private Function FileExists (ByVal FilePath As String ) As Boolean
665636 FileExists = CBool(LenB(Dir(FilePath, vbHidden + vbNormal + vbSystem + vbReadOnly + vbArchive)))
666637End Function
@@ -1305,7 +1276,7 @@ Private Sub GuessInString(ByRef confObject As parserConfig, _
13051276 Dim emptyParam() As Variant
13061277 Dim StartRec As Long
13071278 Dim EndRec As Long
1308- Dim FieldDelStandardDEV () As Double
1279+ Dim CtableScore () As Double
13091280 Dim QuoteChar() As EscapeTokens
13101281 Dim L0_FieldDelimiter As Long
13111282 Dim L1_FieldDelimiter As Long
@@ -1332,7 +1303,7 @@ Private Sub GuessInString(ByRef confObject As parserConfig, _
13321303 tmpDelimiters() = confObject.DelimitersToGuess
13331304 '@--------------------------------------------------------------------------------
13341305 'StdDev array
1335- ReDim FieldDelStandardDEV (LBound(tmpDelimiters) To UBound(tmpDelimiters))
1306+ ReDim CtableScore (LBound(tmpDelimiters) To UBound(tmpDelimiters))
13361307 '@--------------------------------------------------------------------------------
13371308 'String to guess
13381309 If Not Buffered Then
@@ -1376,23 +1347,23 @@ Private Sub GuessInString(ByRef confObject As parserConfig, _
13761347 Set guessResults = New ECPArrayList
13771348 ParseCSVstring CSVstring, confObject, guessResults, emptyParam
13781349 If Not guessResults Is Nothing Then
1379- FieldDelStandardDEV (delIdx) = ArrayListAVGStdDev (guessResults)
1350+ CtableScore (delIdx) = TableScore (guessResults)
13801351 Else
1381- FieldDelStandardDEV (delIdx) = 1.6 E+308
1352+ CtableScore (delIdx) = 1.6 E+308
13821353 End If
13831354 Else
1384- FieldDelStandardDEV (delIdx) = 1.6 E+308
1355+ CtableScore (delIdx) = 1.6 E+308
13851356 End If
13861357 Next delIdx
13871358 '@--------------------------------------------------------------------------------
13881359 'Delimiters discrimination
1389- L1_FieldDelimiter = MinIndexVal(FieldDelStandardDEV )
1360+ L1_FieldDelimiter = MinIndexVal(CtableScore )
13901361 .fieldsDelimiter = tmpDelimiters(L1_FieldDelimiter)
13911362 .startingRecord = StartRec
13921363 .endingRecord = EndRec
13931364 End With
13941365 Erase emptyParam
1395- Erase FieldDelStandardDEV
1366+ Erase CtableScore
13961367 Erase LinesEnds
13971368 Erase QuoteChar
13981369 Erase tmpDelimiters
@@ -2446,6 +2417,24 @@ ParseCSVstring_NoSignificantData:
24462417 "the String has only empty or commented lines that can be omitted."
24472418 Resume ParseCSVstring_Error_Handler
24482419End Sub
2420+ Private Function RecordScore (ByRef strArray As Variant ) As Double
2421+ Dim arrLB As Long
2422+ Dim arrUB As Long
2423+ Dim L0 As Long
2424+ Dim CfieldScore As Double
2425+ Dim CumulativeScore As Double
2426+
2427+ 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
2434+ Exit Function
2435+ RecordScore_ErrHandler:
2436+ RecordScore = 1.6 E+308
2437+ End Function
24492438Private Function RequestedField (ByVal FieldIndex As Long , _
24502439 ByVal mxReq As Long ) As Boolean
24512440 Select Case RequestedFieldsArray(0 )
@@ -3129,6 +3118,16 @@ AdvanceLine:
31293118 End If
31303119 End If
31313120End Sub
3121+ Private Function TableScore (ByRef ArrayList As ECPArrayList ) As Double
3122+ Dim L0 As Long
3123+ Dim StdDevSUM As Double
3124+
3125+ StdDevSUM = 0
3126+ For L0 = 0 To ArrayList.count - 1
3127+ StdDevSUM = StdDevSUM + RecordScore(ArrayList(L0))
3128+ Next L0
3129+ TableScore = StdDevSUM / ArrayList.count
3130+ End Function
31323131Public Sub TwoDimToJaggedArray (ByRef TwoDimArray() As Variant , ByRef JaggedArray() As Variant )
31333132 Dim UBj1 As Long , LBj1 As Long
31343133 Dim UBj2 As Long , LBj2 As Long
@@ -3240,5 +3239,4 @@ Private Function UnixToStandardEscapeSeq(ByRef UnixEscapedString As String, _
32403239 Else
32413240 UnixToStandardEscapeSeq = UnixEscapedString
32423241 End If
3243- End Function
3244-
3242+ End Function
0 commit comments