@@ -238,7 +238,7 @@ Public Sub CloseSeqReader()
238238 Set static_outputList = Nothing
239239End Sub
240240''' <summary>
241- ''' Run a left outer join on the provided data tables.
241+ ''' Run a left, right outer or inner join on the provided data tables.
242242'''' 1) Use a string such as "{1-2,5,ID};{1-6}" as a predicate of the columns to
243243'''' indicate the join of columns 1 to 2, 5 and ID of leftTable with
244244'''' the columns 1 to 6 of rightTable.
@@ -254,38 +254,31 @@ End Sub
254254''' <param name="columns">String that specifies the structure of the rows returned.</param>
255255''' <param name="matchKeys">Priority and preference keys to be matched.</param>
256256''' <param name="predicate">Condition that must be met when selecting rows.</param>
257- ''' <param name="pConfig">CSV parser configuration object .</param>
257+ ''' <param name="headers">Indicates if the tables have headers .</param>
258258''' All indexes must be given IN BASE 1.
259259Public Function tJoin (ByVal nType As JoinType , _
260260 ByRef leftTable As CSVArrayList , _
261261 ByRef rightTable As CSVArrayList , _
262- columns As String , _
262+ Columns As String , _
263263 matchKeys As String , _
264264 Optional predicate As String = vbNullString, _
265- Optional ByRef pConfig As CSVparserConfig ) As CSVArrayList
265+ Optional headers As Boolean = True ) As CSVArrayList
266266
267267 Dim JoinHelper As CSVArrayList
268- Dim tConfig As CSVparserConfig
269-
270- Set JoinHelper = New CSVArrayList
271- If pConfig Is Nothing Then
272- Set tConfig = config
273- Else
274- Set tConfig = pConfig
275- End If
268+
276269 Select Case nType
277270 Case JoinType.JT_LeftJoin
278271 Set tJoin = JoinHelper.LeftJoin(leftTable, rightTable, _
279- columns , matchKeys, predicate, _
280- tConfig.Headers )
272+ Columns , matchKeys, predicate, _
273+ headers )
281274 Case JoinType.JT_RightJoin
282275 Set tJoin = JoinHelper.RightJoin(leftTable, rightTable, _
283- columns , matchKeys, predicate, _
284- tConfig.Headers )
276+ Columns , matchKeys, predicate, _
277+ headers )
285278 Case Else
286279 Set tJoin = JoinHelper.InnerJoin(leftTable, rightTable, _
287- columns , matchKeys, predicate, _
288- tConfig.Headers )
280+ Columns , matchKeys, predicate, _
281+ headers )
289282 End Select
290283End Function
291284Private Function JoinKeys (ByRef tList As CSVArrayList , ByRef Keys As Variant , Index As Long ) As String
@@ -308,7 +301,7 @@ Private Function JoinKeys(ByRef tList As CSVArrayList, ByRef Keys As Variant, In
308301End Function
309302Public Function CSVsubsetSplit (filePath As String , _
310303 Optional subsetColumns As Variant = 1 , _
311- Optional Headers As Boolean = True , _
304+ Optional headers As Boolean = True , _
312305 Optional repeatHeaders As Boolean = True , _
313306 Optional streamSize As Long = 20 ) As Collection
314307 Dim CreatedFiles As Collection
@@ -372,9 +365,9 @@ Public Function CSVsubsetSplit(filePath As String, _
372365 '@----------------------------------------------------
373366 'Parse string
374367 With readerConf
375- .Headers = Headers
368+ .headers = headers
376369 .delimitersGuessing = True
377- If Headers Then
370+ If headers Then
378371 .endingRecord = 1
379372 CSVhead = CSVreader.ImportFromCSV(readerConf)(0 )
380373 .endingRecord = 0
@@ -390,14 +383,14 @@ Public Function CSVsubsetSplit(filePath As String, _
390383 Do While Not CSVstream.atEndOfStream
391384 CSVstream.ReadText 'Read next CSV data chunk
392385 RaiseEvent AfterLoadStream
393- If Headers Then
386+ If headers Then
394387 If fileCreatedFlag Then
395- readerConf.Headers = False
388+ readerConf.headers = False
396389 End If
397390 End If
398391 Set curItems = CSVreader.ImportFromCSVString(CSVstream.bufferString, readerConf).items
399392 If Not fileCreatedFlag Then
400- If Headers Then
393+ If headers Then
401394 i = 1
402395 Else
403396 i = 0
@@ -409,7 +402,7 @@ Public Function CSVsubsetSplit(filePath As String, _
409402 RaiseEvent AfterSort
410403 tmpVar = JoinKeys(curItems, subsetColumns, i)
411404 writterConf.path = OutputPath & CStr(tmpVar) & "." & FExtension
412- If Headers Then
405+ If headers Then
413406 '@----------------------------------------------------
414407 'Check directory
415408 fileOnPathFlag = FileExists(writterConf.path)
@@ -432,7 +425,7 @@ Public Function CSVsubsetSplit(filePath As String, _
432425 ExportSubSet.Reinitialize ExportSubSet.count
433426 tmpVar = JoinKeys(curItems, subsetColumns, i)
434427 writterConf.path = OutputPath & CStr(tmpVar) & "." & FExtension
435- If Headers Then
428+ If headers Then
436429 fileOnPathFlag = FileExists(writterConf.path)
437430 If Not fileOnPathFlag Then
438431 If repeatHeaders Then
@@ -790,7 +783,7 @@ Public Function Filter(Pattern As String, Optional filePath As String = vbNullSt
790783 Else
791784 Set CSVparser = Me
792785 If CSVparser.importSuccess Then
793- ExcludeFirstRecord = (CSVparser.parseConfig.Headers = True )
786+ ExcludeFirstRecord = (CSVparser.parseConfig.headers = True )
794787 Filter.Concat2 CSVparser.items.Filter(Pattern, 1 + Abs(ExcludeFirstRecord), Exclude)
795788 End If
796789 End If
@@ -1492,7 +1485,7 @@ Public Function ImportFromCSV(configObj As CSVparserConfig, _
14921485 Set configObj.dialect = SniffDelimiters(configObj)
14931486 End If
14941487 tmpRequested() = FilterColumns
1495- If .Headers Then
1488+ If .headers Then
14961489 '@--------------------------------------------------------------------------------
14971490 'Read the whole header
14981491 Set P_CSV_HEADER = New CSVArrayList
@@ -1560,7 +1553,7 @@ Public Function ImportFromCSVString(ByRef CSVstring As String, _
15601553 Set configObj.dialect = SniffDelimiters(configObj, CSVstring)
15611554 End If
15621555 tmpRequested() = FilterColumns
1563- If .Headers Then
1556+ If .headers Then
15641557 '@--------------------------------------------------------------------------------
15651558 'Read the header
15661559 Set P_CSV_HEADER = New CSVArrayList
@@ -1619,7 +1612,7 @@ Public Function InsertField(aIndex As Long, Optional FieldName As String = vbNul
16191612 'Reserve storage
16201613 ReDim cpRecord(0 To P_VECTORS_REGULAR_BOUND + 1 )
16211614 With P_CSV_DATA
1622- headerRec = Me.parseConfig.Headers
1615+ headerRec = Me.parseConfig.headers
16231616 For rCounter = 0 To .count - 1
16241617 curRecord() = .Item(rCounter)
16251618 If headerRec Then
@@ -1973,7 +1966,7 @@ End Sub
19731966''' <param name="ExportationBunchSize">The amount of items to export in a single operation.</param>
19741967Public Function SortOnDisk (ByVal filePath As String , _
19751968 Optional ByRef sortingKeys As Variant = 1 , _
1976- Optional Headers As Boolean = True , _
1969+ Optional headers As Boolean = True , _
19771970 Optional streamSize As Single = 20 , _
19781971 Optional ByVal sortAlgorithm As SortingAlgorithms = SortingAlgorithms.SA_Quicksort, _
19791972 Optional ByVal ExportationBunchSize As Long = 10000 ) As String
@@ -2012,7 +2005,7 @@ Public Function SortOnDisk(ByVal filePath As String, _
20122005 FirstStream = True
20132006 Set CSV = New CSVinterface
20142007 With CSV.parseConfig
2015- .Headers = Headers
2008+ .headers = headers
20162009 .endingRecord = 1
20172010 End With
20182011 With inputTextStream
@@ -2031,7 +2024,7 @@ Public Function SortOnDisk(ByVal filePath As String, _
20312024 CSV.parseConfig.endingRecord = 0
20322025 CSV.ImportFromCSVString .bufferString, CSV.parseConfig
20332026 CSV.parseConfig.startingRecord = 1
2034- CSV.parseConfig.Headers = False
2027+ CSV.parseConfig.headers = False
20352028 '@--------------------------------------------------------------------------------
20362029 'Sort and export
20372030 Set sortedFiles = New CSVArrayList
@@ -2063,7 +2056,7 @@ Public Function SortOnDisk(ByVal filePath As String, _
20632056 'Point to target file
20642057 exportConfig.path = OutPutFpath
20652058 'Export header
2066- If Headers Then
2059+ If headers Then
20672060 CSV.ExportToCSV fileHeader, exportConfig, enableDelimitersSniffing:=False
20682061 End If
20692062 ReDim inputTextStreams(0 To sortedFiles.count - 1 )
@@ -2074,7 +2067,7 @@ Public Function SortOnDisk(ByVal filePath As String, _
20742067 Set importConfig = exportConfig.CopyConfig
20752068 With importConfig
20762069 .path = vbNullString
2077- .Headers = False
2070+ .headers = False
20782071 End With
20792072 'Configure readers and parsers
20802073 ComparisonList.Indexing = True
@@ -2290,7 +2283,7 @@ Public Sub OpenSeqReader(configObj As CSVparserConfig, _
22902283 Set configObj.dialect = SniffDelimiters(configObj)
22912284 End If
22922285 static_tmpRequested() = FilterColumns
2293- If .Headers Then
2286+ If .headers Then
22942287 '@--------------------------------------------------------------------------------
22952288 'Read the whole header
22962289 Set P_CSV_HEADER = New CSVArrayList
@@ -2339,7 +2332,7 @@ Public Sub OpenSeqReader(configObj As CSVparserConfig, _
23392332 static_dynamicType = .dynamicTyping
23402333 static_dTTemplate() = .dTypingTemplate
23412334 static_dTTargets() = .dTypingLinks
2342- static_Headers = .Headers
2335+ static_Headers = .headers
23432336 static_IgnoreCommentLines = .skipCommentLines
23442337 static_IgnoreEmptyLines = .skipEmptyLines
23452338 static_IgnoreLines = (static_IgnoreCommentLines Or static_IgnoreEmptyLines)
@@ -2351,7 +2344,7 @@ Public Sub OpenSeqReader(configObj As CSVparserConfig, _
23512344 End With
23522345 static_TokenEndReached = False
23532346 static_RecordEndReached = False
2354- If configObj.Headers Then
2347+ If configObj.headers Then
23552348 Select Case UBound(static_tmpRequested)
23562349 Case -1
23572350 ReDim static_RequestedFieldsArray(0 )
@@ -2537,7 +2530,7 @@ Private Sub ParseCSVstring(ByRef CSVtext As String, _
25372530 ImportDepth = EndRecord - StartRecord + 1 &
25382531 End Select
25392532 If StartRecord = 1 & Then
2540- If configObj.headersOmission And configObj.Headers Then
2533+ If configObj.headersOmission And configObj.headers Then
25412534 If ImportDepth > 1 & Or EndRecord = 0 & Then
25422535 StartRecord = 2 &
25432536 ImportDepth = ImportDepth - 1 &
@@ -3514,7 +3507,7 @@ Public Function Sort(Optional ByVal fromIndex As Long = -1, _
35143507
35153508 If P_SUCCESSFUL_IMPORT Then
35163509 If fromIndex = -1 Then
3517- If config.Headers And Not config.headersOmission Then
3510+ If config.headers And Not config.headersOmission Then
35183511 fromIndex = 2
35193512 Else
35203513 fromIndex = 1
@@ -3747,7 +3740,7 @@ Private Sub StreamParseCSV(configObj As CSVparserConfig, _
37473740 ImportDepth = EndRecord - StartRecord + 1 &
37483741 End Select
37493742 If StartRecord = 1 & Then
3750- If configObj.headersOmission And configObj.Headers Then
3743+ If configObj.headersOmission And configObj.headers Then
37513744 If ImportDepth > 1 & Or EndRecord = 0 & Then
37523745 StartRecord = 2 &
37533746 ImportDepth = ImportDepth - 1 &
@@ -4450,4 +4443,5 @@ Private Function UnixToStandardEscapeSeq(ByRef UnixEscapedString As String, _
44504443 Else
44514444 UnixToStandardEscapeSeq = UnixEscapedString
44524445 End If
4453- End Function
4446+ End Function
4447+
0 commit comments