Skip to content

Commit b51a05e

Browse files
committed
Fixed joins error
Joins did not retrieve headers
1 parent 05b7f4f commit b51a05e

File tree

1 file changed

+72
-18
lines changed

1 file changed

+72
-18
lines changed

src/CSVArrayList.cls

Lines changed: 72 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -873,7 +873,7 @@ End Function
873873
Public Function Group(Table As CSVArrayList, By As Variant, OperateOn As Variant, _
874874
Optional Alias As String = vbNullString, _
875875
Optional AggregateFunct As AggregateFunctions = AggregateFunctions.AF_Summary, _
876-
Optional Headers As Boolean = True) As CSVArrayList
876+
Optional headers As Boolean = True) As CSVArrayList
877877
On Error GoTo grop_errHandler
878878
Dim deltaPos As Long
879879
Dim gAvg As Double
@@ -904,7 +904,7 @@ Public Function Group(Table As CSVArrayList, By As Variant, OperateOn As Variant
904904
Set Group = New CSVArrayList
905905
'Save fields indexes
906906
If Not IsNumeric(By) Then
907-
If Headers Then
907+
If headers Then
908908
GroupFIdx = GetColumnIndex(CStr(By), Table.Item(0)) - deltaPos + 1
909909
Else
910910
GroupFIdx = 1 'Base 1 input
@@ -913,7 +913,7 @@ Public Function Group(Table As CSVArrayList, By As Variant, OperateOn As Variant
913913
GroupFIdx = Abs(By)
914914
End If
915915
If Not IsNumeric(OperateOn) Then
916-
If Headers Then
916+
If headers Then
917917
OperateFidx = GetColumnIndex(CStr(OperateOn), Table.Item(0)) - deltaPos + 1
918918
Else
919919
OperateFidx = 1 'Base 1 input
@@ -922,7 +922,7 @@ Public Function Group(Table As CSVArrayList, By As Variant, OperateOn As Variant
922922
OperateFidx = Abs(OperateOn)
923923
End If
924924
'Save first row
925-
If Headers Then
925+
If headers Then
926926
tmpRow(0) = Table.Item(0)(GroupFIdx + deltaPos - 1)
927927
If AggregateFunct <> AggregateFunctions.AF_Summary Then
928928
If Alias <> vbNullString Then
@@ -942,15 +942,15 @@ Public Function Group(Table As CSVArrayList, By As Variant, OperateOn As Variant
942942
'Sort the data if needed
943943
If Table.IsSorted Then
944944
If LAST_SORTED_FIELD <> GroupFIdx Then 'Sorting required
945-
tmpData = Table.Copy.Sort(fromIndex:=1 + Abs(Headers), sortingKeys:=GroupFIdx + deltaPos).items
945+
tmpData = Table.Copy.Sort(fromIndex:=1 + Abs(headers), sortingKeys:=GroupFIdx + deltaPos).items
946946
Else
947947
tmpData = Table.Copy.items
948948
End If
949949
Else
950-
tmpData = Table.Copy.Sort(fromIndex:=1 + Abs(Headers), sortingKeys:=GroupFIdx + deltaPos).items
950+
tmpData = Table.Copy.Sort(fromIndex:=1 + Abs(headers), sortingKeys:=GroupFIdx + deltaPos).items
951951
End If
952952
'Compute agregates
953-
If Headers Then
953+
If headers Then
954954
iCounter = LBound(tmpData) + 1 'Headers worked yet
955955
Else
956956
iCounter = LBound(tmpData)
@@ -1484,7 +1484,7 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
14841484
Columns As String, _
14851485
matchKeys As String, _
14861486
Optional predicate As String = vbNullString, _
1487-
Optional Headers As Boolean = True) As CSVArrayList
1487+
Optional headers As Boolean = True) As CSVArrayList
14881488

14891489
Dim cColumns() As String
14901490
Dim cKeys() As String
@@ -1510,6 +1510,7 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
15101510
Dim rightIdxDelta As Long
15111511
Dim sCounter As Long
15121512
Dim tmpIndex As Long
1513+
Dim WrittenHeaders As Boolean
15131514

15141515
On Error GoTo join_errHandler
15151516
If leftTable.Indexing Or rightTable.Indexing Then Exit Function 'Not available for indexed lists
@@ -1540,7 +1541,7 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
15401541
FillReqFlds fullReqFields, lftTableReqFlds, leftIdxDelta, leftIdxDelta
15411542
FillReqFlds fullReqFields, rgtTableReqFlds, LftTblENDidx + 1, leftIdxDelta
15421543
Set refTable = rightTable.Copy
1543-
refTable.Sort 1 + Abs(Headers), sortingKeys:=CLng(cKeys(UBound(cKeys))) + rightIdxDelta 'Sort the right table
1544+
refTable.Sort 1 + Abs(headers), sortingKeys:=CLng(cKeys(UBound(cKeys))) + rightIdxDelta 'Sort the right table
15441545
Set exprHelper = New CSVexpressions
15451546
With exprHelper
15461547
If predicate <> vbNullString Then
@@ -1554,7 +1555,7 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
15541555
.Create cPredicate
15551556
FilterFields() = GetIndexesFromVarList(.CurrentVariables)
15561557
End If
1557-
For rCounter = Abs(Headers) To leftTable.count - 1
1558+
For rCounter = Abs(headers) To leftTable.count - 1
15581559
'Initial configurations
15591560
MatchesForCurrentKey.Clear
15601561
MatchCounter = 0
@@ -1581,6 +1582,23 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
15811582
MatchesForCurrentKey.Add -1
15821583
End If
15831584
Do
1585+
If headers Then
1586+
If Not WrittenHeaders Then
1587+
' Fill headers on left
1588+
For sCounter = 0 To LftTblENDidx
1589+
resultRecord(sCounter) = leftTable(0)(lftTableReqFlds(sCounter) _
1590+
+ leftIdxDelta - 1)
1591+
Next sCounter
1592+
' Fill headers on right
1593+
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
1594+
resultRecord(sCounter) = refTable(0)(rgtTableReqFlds(sCounter - _
1595+
(LftTblENDidx + 1)) + rightIdxDelta - 1)
1596+
Next sCounter
1597+
LeftJoin.Add resultRecord 'Append current record
1598+
WrittenHeaders = True
1599+
resultRecord() = resultRecord_BK
1600+
End If
1601+
End If
15841602
'Fill left table data
15851603
For sCounter = 0 To LftTblENDidx
15861604
resultRecord(sCounter) = leftTable(rCounter)(lftTableReqFlds(sCounter) _
@@ -1597,7 +1615,7 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
15971615
If .ErrorType = ExpressionErrors.errNone Then
15981616
If err.Number = 0 Then
15991617
If CBool(.result) Then
1600-
'Fill in the data in the table on the left only if the join and predicate are satisfied.
1618+
'Fill in the data in the table on the right only if the join and predicate are satisfied.
16011619
If lJoinIndex > -1 Then
16021620
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
16031621
resultRecord(sCounter) = refTable(lJoinIndex)(rgtTableReqFlds(sCounter - _
@@ -1610,7 +1628,7 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
16101628
End If
16111629
End If
16121630
Else
1613-
'Fill in the data in the table on the left only if the join is satisfied.
1631+
'Fill in the data in the table on the right only if the join is satisfied.
16141632
If lJoinIndex > -1 Then
16151633
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
16161634
resultRecord(sCounter) = refTable(lJoinIndex)(rgtTableReqFlds(sCounter - _
@@ -1653,7 +1671,7 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
16531671
Columns As String, _
16541672
matchKeys As String, _
16551673
Optional predicate As String = vbNullString, _
1656-
Optional Headers As Boolean = True) As CSVArrayList
1674+
Optional headers As Boolean = True) As CSVArrayList
16571675
On Error GoTo join_errHandler
16581676
Dim cColumns() As String
16591677
Dim cKeys() As String
@@ -1679,6 +1697,7 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
16791697
Dim rightIdxDelta As Long
16801698
Dim sCounter As Long
16811699
Dim tmpIndex As Long
1700+
Dim WrittenHeaders As Boolean
16821701

16831702
If leftTable.Indexing Or rightTable.Indexing Then Exit Function 'Not available for indexed lists
16841703
Set RightJoin = New CSVArrayList
@@ -1708,7 +1727,7 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
17081727
FillReqFlds fullReqFields, lftTableReqFlds, leftIdxDelta, leftIdxDelta
17091728
FillReqFlds fullReqFields, rgtTableReqFlds, LftTblENDidx + 1, leftIdxDelta
17101729
Set refTable = leftTable.Copy
1711-
refTable.Sort 1 + Abs(Headers), sortingKeys:=CLng(cKeys(LBound(cKeys))) + leftIdxDelta 'Sort the left table
1730+
refTable.Sort 1 + Abs(headers), sortingKeys:=CLng(cKeys(LBound(cKeys))) + leftIdxDelta 'Sort the left table
17121731
Set exprHelper = New CSVexpressions
17131732
With exprHelper
17141733
If predicate <> vbNullString Then
@@ -1722,7 +1741,7 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
17221741
.Create cPredicate
17231742
FilterFields() = GetIndexesFromVarList(.CurrentVariables)
17241743
End If
1725-
For rCounter = Abs(Headers) To rightTable.count - 1
1744+
For rCounter = Abs(headers) To rightTable.count - 1
17261745
'Initial configurations
17271746
MatchesForCurrentKey.Clear
17281747
MatchCounter = 0
@@ -1749,6 +1768,23 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
17491768
MatchesForCurrentKey.Add -1
17501769
End If
17511770
Do
1771+
If headers Then
1772+
If Not WrittenHeaders Then
1773+
' Fill headers on right
1774+
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
1775+
resultRecord(sCounter) = rightTable(0)(rgtTableReqFlds(sCounter - _
1776+
(LftTblENDidx + 1)) + rightIdxDelta - 1)
1777+
Next sCounter
1778+
' Fill headers on left
1779+
For sCounter = 0 To LftTblENDidx
1780+
resultRecord(sCounter) = refTable(0)(lftTableReqFlds(sCounter) _
1781+
+ leftIdxDelta - 1)
1782+
Next sCounter
1783+
RightJoin.Add resultRecord 'Append current record
1784+
WrittenHeaders = True
1785+
resultRecord() = resultRecord_BK
1786+
End If
1787+
End If
17521788
'Fill right table data
17531789
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
17541790
resultRecord(sCounter) = rightTable(rCounter)(rgtTableReqFlds(sCounter - _
@@ -1821,7 +1857,7 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
18211857
Columns As String, _
18221858
matchKeys As String, _
18231859
Optional predicate As String = vbNullString, _
1824-
Optional Headers As Boolean = True) As CSVArrayList
1860+
Optional headers As Boolean = True) As CSVArrayList
18251861

18261862
Dim cColumns() As String
18271863
Dim cKeys() As String
@@ -1847,6 +1883,7 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
18471883
Dim rightIdxDelta As Long
18481884
Dim sCounter As Long
18491885
Dim tmpIndex As Long
1886+
Dim WrittenHeaders As Boolean
18501887

18511888
If leftTable.Indexing Or rightTable.Indexing Then Exit Function 'Not available for indexed lists
18521889
Set InnerJoin = New CSVArrayList
@@ -1876,7 +1913,7 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
18761913
FillReqFlds fullReqFields, lftTableReqFlds, leftIdxDelta, leftIdxDelta
18771914
FillReqFlds fullReqFields, rgtTableReqFlds, LftTblENDidx + 1, leftIdxDelta
18781915
Set refTable = rightTable.Copy
1879-
refTable.Sort 1 + Abs(Headers), sortingKeys:=CLng(cKeys(UBound(cKeys))) + rightIdxDelta 'Sort the right table
1916+
refTable.Sort 1 + Abs(headers), sortingKeys:=CLng(cKeys(UBound(cKeys))) + rightIdxDelta 'Sort the right table
18801917
Set exprHelper = New CSVexpressions
18811918
With exprHelper
18821919
If predicate <> vbNullString Then
@@ -1890,7 +1927,7 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
18901927
.Create cPredicate
18911928
FilterFields() = GetIndexesFromVarList(.CurrentVariables)
18921929
End If
1893-
For rCounter = Abs(Headers) To leftTable.count - 1
1930+
For rCounter = Abs(headers) To leftTable.count - 1
18941931
'Initial configurations
18951932
MatchesForCurrentKey.Clear
18961933
MatchCounter = 0
@@ -1917,6 +1954,23 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
19171954
MatchesForCurrentKey.Add -1
19181955
End If
19191956
Do
1957+
If headers Then
1958+
If Not WrittenHeaders Then
1959+
' Fill headers on left
1960+
For sCounter = 0 To LftTblENDidx
1961+
resultRecord(sCounter) = leftTable(0)(lftTableReqFlds(sCounter) _
1962+
+ leftIdxDelta - 1)
1963+
Next sCounter
1964+
' Fill headers on right
1965+
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
1966+
resultRecord(sCounter) = refTable(0)(rgtTableReqFlds(sCounter - _
1967+
(LftTblENDidx + 1)) + rightIdxDelta - 1)
1968+
Next sCounter
1969+
InnerJoin.Add resultRecord 'Append current record
1970+
WrittenHeaders = True
1971+
resultRecord() = resultRecord_BK
1972+
End If
1973+
End If
19201974
lJoinIndex = MatchesForCurrentKey(MatchCounter)
19211975
If predicate <> vbNullString Then
19221976
FillReqFlds evalRecord, leftTable(rCounter), leftIdxDelta, leftIdxDelta

0 commit comments

Comments
 (0)