@@ -448,18 +448,9 @@ Public Sub DumpToArray(OutPutArray() As Variant, _
448448 Set DataSource = P_CSV_DATA
449449 End If
450450 If Not DataSource Is Nothing Then
451- Dim UB1 As Long , ub2 As Long
452- Dim Counter1 As Long , Counter2 As Long
453-
454- UB1 = DataSource.count - 1
455- ReDim OutPutArray(0 To UB1, 0 To P_VECTORS_MAX_BOUND)
456-
457- For Counter1 = 0 To UB1
458- ub2 = UBound(DataSource(Counter1))
459- For Counter2 = 0 To ub2
460- OutPutArray(Counter1, Counter2) = DataSource(Counter1)(Counter2)
461- Next Counter2
462- Next Counter1
451+ Dim tmpOutputArray() As Variant
452+ tmpOutputArray = DataSource.items
453+ DataSource.JaggedToTwoDimArray tmpOutputArray, OutPutArray
463454 End If
464455End Sub
465456Public Sub DumpToJaggedArray (OutPutArray() As Variant , _
@@ -468,15 +459,7 @@ Public Sub DumpToJaggedArray(OutPutArray() As Variant, _
468459 Set DataSource = P_CSV_DATA
469460 End If
470461 If Not DataSource Is Nothing Then
471- Dim UB1 As Long
472- Dim Counter1 As Long
473-
474- UB1 = DataSource.count - 1
475- ReDim OutPutArray(0 To UB1)
476-
477- For Counter1 = 0 To UB1
478- OutPutArray(Counter1) = DataSource(Counter1)
479- Next Counter1
462+ OutPutArray() = DataSource.items
480463 End If
481464End Sub
482465Public Sub DumpToSheet (Optional WBookName As String , _
@@ -517,19 +500,15 @@ Public Sub DumpToSheet(Optional WBookName As String, _
517500 End If
518501 '@------------------------------------------------------
519502 'Dump the data
520- Dim tmpOutputArray() As String
521- Dim UB1 As Long , ub2 As Long
503+ Dim tmpOutputArray() As Variant
504+ Dim UB1 As Long , UB2 As Long
522505 Dim Counter1 As Long , Counter2 As Long
506+ Dim OutPutArr() As Variant
523507
524508 UB1 = DataSource.count - 1
525- ReDim tmpOutputArray(0 To UB1, 0 To colNumber)
526-
527- For Counter1 = 0 To UB1
528- ub2 = UBound(DataSource(Counter1))
529- For Counter2 = 0 To ub2
530- tmpOutputArray(Counter1, Counter2) = DataSource(Counter1)(Counter2)
531- Next Counter2
532- Next Counter1
509+ tmpOutputArray() = DataSource.items
510+ DataSource.JaggedToTwoDimArray tmpOutputArray, OutPutArr
511+
533512 '@------------------------------------------------------
534513 'Set the target Range
535514 Set OutputRange = outputSheet.Range(rngName) _
@@ -538,8 +517,9 @@ Public Sub DumpToSheet(Optional WBookName As String, _
538517 UB1 + 1 , _
539518 colNumber + 1 _
540519 )
541- OutputRange.Value2 = tmpOutputArray
520+ OutputRange.Value2 = OutPutArr
542521 Erase tmpOutputArray
522+ Erase OutPutArr
543523 EnableOptimization False
544524 End If
545525End Sub
@@ -1750,8 +1730,9 @@ Private Function JoinRecordsFields(ByRef RecordsArray As Variant, _
17501730 Dim QuoteT As QuoteTokens
17511731 Dim FldDelimiter As String
17521732 Dim iLCounter As Long , jLCounter As Long
1733+ Dim JaggedRecordsArray() As Variant
17531734 Dim LB1 As Long , UB1 As Long
1754- Dim LB2 As Long , ub2 As Long
1735+ Dim LB2 As Long , UB2 As Long
17551736 Dim recDelimiter As String
17561737 Dim arrayHelper As CSVArrayList
17571738
@@ -1781,6 +1762,7 @@ Private Function JoinRecordsFields(ByRef RecordsArray As Variant, _
17811762 EscapeSequence = CoerceChr & CoerceChr
17821763 Dim tmpBuffer As Variant
17831764 If LCase(TypeName(RecordsArray)) = "csvarraylist" Then
1765+ JaggedRecordsArray() = RecordsArray.items
17841766 '@----------------------------------------------------------------------------
17851767 'Set array sizes
17861768 LB1 = 0
@@ -1789,11 +1771,11 @@ Private Function JoinRecordsFields(ByRef RecordsArray As Variant, _
17891771 '@----------------------------------------------------------------------------
17901772 'Concatenate fields
17911773 For iLCounter = LB1 To UB1
1792- tmpBuffer = RecordsArray (iLCounter)
1774+ tmpBuffer = JaggedRecordsArray (iLCounter)
17931775 LB2 = LBound(tmpBuffer)
1794- ub2 = UBound(tmpBuffer)
1795- ReDim Buffer(LB2 To ub2 )
1796- For jLCounter = LB2 To ub2
1776+ UB2 = UBound(tmpBuffer)
1777+ ReDim Buffer(LB2 To UB2 )
1778+ For jLCounter = LB2 To UB2
17971779 Buffer(jLCounter) = tmpBuffer(jLCounter)
17981780 If UseUnixEscapeSeq Then
17991781 UnixEscapeField Buffer(jLCounter), CoerceChr, FldDelimiter, _
@@ -1816,15 +1798,15 @@ Private Function JoinRecordsFields(ByRef RecordsArray As Variant, _
18161798 LB1 = LBound(RecordsArray, 1 )
18171799 LB2 = LBound(RecordsArray, 2 )
18181800 UB1 = UBound(RecordsArray, 1 )
1819- ub2 = UBound(RecordsArray, 2 )
1801+ UB2 = UBound(RecordsArray, 2 )
18201802 '@----------------------------------------------------------------------------
18211803 'Set array sizes
18221804 ReDim ConcatenatedArray(LB1 To UB1)
1823- ReDim Buffer(LB2 To ub2 )
1805+ ReDim Buffer(LB2 To UB2 )
18241806 '@----------------------------------------------------------------------------
18251807 'Concatenate fields
18261808 For iLCounter = LB1 To UB1
1827- For jLCounter = LB2 To ub2
1809+ For jLCounter = LB2 To UB2
18281810 Buffer(jLCounter) = RecordsArray(iLCounter, jLCounter)
18291811 If UseUnixEscapeSeq Then
18301812 UnixEscapeField Buffer(jLCounter), CoerceChr, FldDelimiter, _
@@ -1882,9 +1864,9 @@ Private Function JoinRecordsFields(ByRef RecordsArray As Variant, _
18821864 For iLCounter = LB1 To UB1
18831865 tmpBuffer = RecordsArray(iLCounter)
18841866 LB2 = LBound(tmpBuffer)
1885- ub2 = UBound(tmpBuffer)
1886- ReDim Buffer(LB2 To ub2 )
1887- For jLCounter = LB2 To ub2
1867+ UB2 = UBound(tmpBuffer)
1868+ ReDim Buffer(LB2 To UB2 )
1869+ For jLCounter = LB2 To UB2
18881870 Buffer(jLCounter) = tmpBuffer(jLCounter)
18891871 If UseUnixEscapeSeq Then
18901872 UnixEscapeField Buffer(jLCounter), CoerceChr, FldDelimiter, _
0 commit comments