@@ -597,15 +597,15 @@ Public Function GetCSVsubset(FilePath As String, _
597597 keyIndex As Long , _
598598 Optional configObj As parserConfig = Nothing ) As ECPArrayList
599599
600- Dim streamReader As ECPTextStream
600+ Dim StreamReader As ECPTextStream
601601 Dim curItems As ECPArrayList
602602 Dim filteredRecords As ECPArrayList
603603 Dim CSVparser As CSVinterface
604604 Dim gssCounter As Long
605605
606606 Set CSVparser = New CSVinterface
607607 Set filteredRecords = New ECPArrayList
608- Set streamReader = New ECPTextStream
608+ Set StreamReader = New ECPTextStream
609609 On Error GoTo CSVsubset_ErrHandler
610610 If FilePath <> vbNullString Then
611611 '@----------------------------------------------------
@@ -628,7 +628,7 @@ Public Function GetCSVsubset(FilePath As String, _
628628 LB = LBound(queryFilters)
629629 '@----------------------------------------------------
630630 ' Sequential reading from file
631- With streamReader
631+ With StreamReader
632632 .endStreamOnLineBreak = True
633633 .OpenStream FilePath
634634 .ReadText
@@ -642,7 +642,7 @@ Public Function GetCSVsubset(FilePath As String, _
642642 CSVparser.GuessDelimiters configObj
643643 '@----------------------------------------------------
644644 ' Parse string
645- Set curItems = CSVparser.ImportFromCSVString(streamReader .bufferString, configObj).items
645+ Set curItems = CSVparser.ImportFromCSVString(StreamReader .bufferString, configObj).items
646646 If configObj.headers Then
647647 filteredRecords.Add curItems(0 ) 'Save the CSV header
648648 gssCounter = gssCounter + 1
@@ -652,9 +652,9 @@ Public Function GetCSVsubset(FilePath As String, _
652652 filteredRecords.Add curItems(gssCounter) 'Append data
653653 End If
654654 Next gssCounter
655- Do While Not streamReader .atEndOfStream
656- streamReader .ReadText 'Read next CSV data chunk
657- Set curItems = CSVparser.ImportFromCSVString(streamReader .bufferString, configObj).items
655+ Do While Not StreamReader .atEndOfStream
656+ StreamReader .ReadText 'Read next CSV data chunk
657+ Set curItems = CSVparser.ImportFromCSVString(StreamReader .bufferString, configObj).items
658658 For gssCounter = 0 To curItems.count - 1
659659 If MeetsCriterion(curItems(gssCounter)(keyIndex)) Then
660660 filteredRecords.Add curItems(gssCounter) 'Append data
@@ -665,7 +665,7 @@ Public Function GetCSVsubset(FilePath As String, _
665665 Set filteredRecords = Nothing
666666 Set CSVparser = Nothing
667667 Set curItems = Nothing
668- Set streamReader = Nothing
668+ Set StreamReader = Nothing
669669 End If
670670 P_SUCCESSFUL_IMPORT = True
671671 Else
@@ -674,7 +674,7 @@ Public Function GetCSVsubset(FilePath As String, _
674674 ResetAlerts
675675 Exit Function
676676CSVsubset_ErrHandler:
677- Set streamReader = Nothing
677+ Set StreamReader = Nothing
678678 Set CSVparser = Nothing
679679 Set curItems = Nothing
680680 Exit Function
@@ -1320,7 +1320,7 @@ Public Function ImportFromCSV(configObj As parserConfig, _
13201320 P_SUCCESSFUL_IMPORT = False
13211321 P_ERROR_DESC = "[CSV file Import]: the config object has an invalid Dynamic Typing Template (DTT). " _
13221322 & "The number of Dynamic Typing Links (DTL) must be less or equal than the number of " _
1323- & "the Dynamic Typing Targets Fields(DTTF) fields defined."
1323+ & "Dynamic Typing Targets Fields (DTTF) defined."
13241324 P_ERROR_NUMBER = vbObjectError + 9007
13251325 P_ERROR_SOURCE = "CSVinterface"
13261326 End If
@@ -1391,7 +1391,7 @@ Public Function ImportFromCSVString(ByRef CSVstring As String, _
13911391 P_SUCCESSFUL_IMPORT = False
13921392 P_ERROR_DESC = "[CSV String Import]: the config object has an invalid Dynamic Typing Template (DTT). " _
13931393 & "The number of Dynamic Typing Links (DTL) must be less or equal than the number of " _
1394- & "the Dynamic Typing Targets Fields(DTTF) fields defined."
1394+ & "Dynamic Typing Targets Fields(DTTF) defined."
13951395 P_ERROR_NUMBER = vbObjectError + 9007
13961396 P_ERROR_SOURCE = "CSVinterface"
13971397 End If
@@ -1760,7 +1760,7 @@ Public Sub OpenSeqReader(configObj As parserConfig, _
17601760 P_SUCCESSFUL_IMPORT = False
17611761 P_ERROR_DESC = "the config object has an invalid Dynamic Typing Template (DTT). " _
17621762 & "The number of Dynamic Typing Links (DTL) must be less or equal than the number of " _
1763- & "the Dynamic Typing Targets Fields(DTTF) fields defined."
1763+ & "Dynamic Typing Targets Fields(DTTF) defined."
17641764 P_ERROR_NUMBER = vbObjectError + 9007
17651765 P_ERROR_SOURCE = "CSVinterface"
17661766 GoTo OpenSeqReader_Error_Handler
@@ -2320,8 +2320,8 @@ ParseCSVstring_MissingEscapeChar:
23202320ParseCSVstring_NoSignificantData:
23212321 Err.Raise Number:=vbObjectError + 9010 , _
23222322 Source:="CSVinterface Class [ParseCSVstring]" , _
2323- Description:="The CSV file has no significant data. This can occur when " & _
2324- "the file has only empty or commented lines that can be omitted."
2323+ Description:="The String has no significant data. This can occur when " & _
2324+ "the String has only empty or commented lines that can be omitted."
23252325 Resume ParseCSVstring_Error_Handler
23262326End Sub
23272327
0 commit comments