@@ -10,50 +10,18 @@ Attribute VB_Exposed = False
1010'#
1111'////////////////////////////////////////////////////////////////////////////////////////////
1212' Copyright © 2020 W. García
13- ' GPL-3.0 license | https://github.com/ws-garcia /
13+ ' GPL-3.0 license | https://www.gnu.org/licenses/gpl-3.0.html /
1414' https://ingwilfredogarcia.wordpress.com
1515'#
16- ' This program is free software: you can redistribute it and/or modify it under the terms of
17- ' the GNU General Public License as published by the Free Software Foundation, either
18- ' version 3 of the License, or (at your option) any later version.
19- '#
20- ' This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY;
21- ' without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
22- ' See the GNU General Public License for more details.
23- '#
24- ' You should have received a copy of the GNU General Public License along with this program.
25- ' If not, see https://www.gnu.org/licenses/gpl-3.0.html.
26- '#
2716'////////////////////////////////////////////////////////////////////////////////////////////
2817' GENERAL INFO:
29- ' This class is inspired in a work available in
30- ' https://www.freevbcode.com/ShowCode.asp?ID=3110. The class module was designed and tested
31- ' using Windows 7® and is supose to work as well over more recent Microsoft™ operative
32- ' system.
33- '#
34- ' Use CSVinterface class to simplify the work with comma separated value (CSV) files.
35- ' It allow you to exchange information betwen an VBA array and an external CSV file without
36- ' using Excel Worksheets, neigter any external reference such as [MS Scripting Runtime].
37- ' The class develop is focusing in the code execution performance.
18+ ' RFC-4180 compliant class module that allows users exchange data between VBA arrays and
19+ ' CSV files at high speed.
3820'#
3921' Feel free to visit the cited websites to explore some of the available solutions for
4022' work with CSV files and VBA Arrays.
4123'////////////////////////////////////////////////////////////////////////////////////////////
4224'#
43- '////////////////////////////////////////////////////////////////////////////////////////////
44- ' USAGE:
45- ' #1- Create an instance of the class [Dim CSVix As CSVinterface]
46- ' #2- Connect to CSV [CSVix.OpenConnection] using the full path to the target file.
47- ' #3- Call the desired method
48- ' CSVix.ImportFromCSV
49- ' CSVix.ExportToCSV
50- ' #4- Declare a String Array [Dim ArrayOne() As String]
51- ' #5- Dump the class content to the array using the [CSVix.DumpToArray(ArrayOne)] method call.
52- '
53- ' NOTE: you can modify the default value for the properties [FieldsDelimiter], [CoercType],
54- ' [StartingRecord] and [EndingRecord] to alter the way the class works.
55- '////////////////////////////////////////////////////////////////////////////////////////////
56- '#
5725' CREDITS:
5826' Although this class have original pieces of code and logic, it use code,
5927' or hints, of many authors. Visit the web sources listed below:
@@ -77,7 +45,6 @@ Private Const CHR_APOSTROPHE As String = "'"
7745Private Const CHR_COMMA As String = ","
7846Private Const CHR_DOUBLE_QUOTES As String = """"
7947Private Const CHR_SEMICOLON As String = ";"
80- Private Const CHR_SPACE As String = " "
8148'////////////////////////////////////////////////////////////////////////////////////////////
8249'#
8350'////////////////////////////////////////////////////////////////////////////////////////////
@@ -211,8 +178,8 @@ Public Property Get QuotingMode() As QuotationMode
211178Attribute QuotingMode.VB_Description = "Gets or sets the mode used for fields quoting."
212179 QuotingMode = P_QUOTING_MODE
213180End Property
214- Public Property Let QuotingMode(Mode As QuotationMode )
215- P_QUOTING_MODE = Mode
181+ Public Property Let QuotingMode(mode As QuotationMode )
182+ P_QUOTING_MODE = mode
216183End Property
217184Public Property Get RecordsDelimiter() As String
218185Attribute RecordsDelimiter.VB_Description = "Gets or sets the char used as delimiter for the CSV file records in the current instance."
@@ -289,8 +256,7 @@ Attribute CreateJagged.VB_Description = "Creates an empty array of vectors, each
289256End Sub
290257Private Function CSVcolumns (csvArray() As String , _
291258 Optional FieldsDelimiter As String = CHR_COMMA) As Long
292- Attribute CSVcolumns.VB_Description = "Computes fields amount for a CSV file in which each fields is surrounded by quotes."
293- Dim iCounter As Long
259+ Attribute CSVcolumns.VB_Description = "Computes fields amount for a CSV file Only works with the ParseCSV method."
294260 Dim LB As Long , UB As Long
295261 Dim lngPos As Long
296262 Dim MDCounter As Long
@@ -409,7 +375,7 @@ Attribute DumpToSheet.VB_Description = "Dumps the CSV data from the current inst
409375 End If
410376End Sub
411377Private Sub EnableOptimization (Optional Optimize As Boolean = True )
412- Attribute EnableOptimization.VB_Description = "Turns On and Off the optimized over an Excel Worksheet data dumping ."
378+ Attribute EnableOptimization.VB_Description = "Turns On and Off data-dump operation optimization over an Excel Worksheet."
413379 If Optimize Then
414380 '@------------------------------------------------------
415381 'Optimize resource consumption
@@ -456,7 +422,7 @@ ErrHandler_ExportToCSV:
456422 P_ERROR_DESC = "[CSV file Export]: " & P_ERROR_DESC
457423End Sub
458424Private Function FileExists (ByVal filePath As String ) As Boolean
459- Attribute FileExists.VB_Description = "Determines if a file exist in the path specified."
425+ Attribute FileExists.VB_Description = "Determines if the file exist in the specified path ."
460426 FileExists = CBool(LenB(Dir(filePath, vbHidden + vbNormal + vbSystem + vbReadOnly + vbArchive)))
461427End Function
462428Private Sub GetCSVtext (ByRef OutPutVar As String )
@@ -497,7 +463,7 @@ End Function
497463Private Function GetRecordIndex (ByVal RecordIndex As Long , _
498464 ByRef CSVdataArray() As String , _
499465 ByRef MaxIndex As Long ) As Long
500- Attribute GetRecordIndex.VB_Description = "Returns the Index in wich the record will start."
466+ Attribute GetRecordIndex.VB_Description = "Returns the Index in wich the specified record will start."
501467 Dim ASCIIcharw As Long
502468 Dim EscapedWFS As Boolean
503469 Dim EscapeAscW As Long
@@ -788,7 +754,7 @@ IsJaggedArray_Err_Handler:
788754 IsJaggedArray = False
789755End Function
790756Private Function IsSheetInWorkbook (SheetName As String , WBook As Workbook ) As Boolean
791- Attribute IsSheetInWorkbook.VB_Description = "Checks if the given sheet is part of the given or of the active one Workbook."
757+ Attribute IsSheetInWorkbook.VB_Description = "Checks if the given sheet is part of the given Workbook."
792758 With WBook
793759 On Error Resume Next
794760 IsSheetInWorkbook = (.Sheets(SheetName).Name = SheetName)
@@ -1072,26 +1038,21 @@ ErrHandler_OpenConnection:
10721038End Sub
10731039Private Sub ParseCriticalCSV (ByRef csvText As String , _
10741040 Optional HeadersOmission As Boolean = False )
1075- Attribute ParseCriticalCSV.VB_Description = "Parses text strings CSV’s compliant with the RFC-4180 specs."
1041+ Attribute ParseCriticalCSV.VB_Description = "Parses text strings CSVs checking the RFC-4180 specs."
10761042 Dim ASCIIcharw As Long
10771043 Dim buffer() As String
1078- Dim Counter1 As Long
10791044 Dim CurrentBufferIndex As Long
10801045 Dim CurrentRecordSize As Long
10811046 Dim CurrenttmpTokenIndex As Long
10821047 Dim EndRecord As Long
10831048 Dim EscapedWFS As Boolean
10841049 Dim EscapeAscW As Long
10851050 Dim EscapeChr As String
1086- Dim FieldsAmount As Long
1087- Dim FieldsCount As Long
10881051 Dim FDAscW As Long
10891052 Dim HeaderSize As Long
10901053 Dim index As Long , MaxIndex As Long
10911054 Dim ImportDepth As Long
1092- Dim JaggedDepth() As String
10931055 Dim LenCurrentIndex As Long
1094- Dim LenFile As Long
10951056 Dim MaxBufferIndex As Long
10961057 Dim MaxtmpTokenIndex As Long
10971058 Dim OpenedToken As Boolean
@@ -1112,7 +1073,6 @@ Attribute ParseCriticalCSV.VB_Description = "Parses text strings CSV
11121073 '@----------------------------------------------------------------------------
11131074 'Start variables
11141075 SearchBeginningMark = 1 &
1115- FieldsCount = 0 &
11161076 RecordsCount = 0 &
11171077 P_MAX_JAGG_INDEX = 0 &
11181078 MaxBufferIndex = 127
@@ -1126,7 +1086,6 @@ Attribute ParseCriticalCSV.VB_Description = "Parses text strings CSV
11261086 '@----------------------------------------------------------------------------
11271087 'Set variables
11281088 OverStringPointer = SearchBeginningMark
1129- LenFile = LenB(csvText)
11301089 ASCIIcharw = AscW(csvText)
11311090 '@----------------------------------------------------------------------------
11321091 'Split the content using the records delimiter char
@@ -1374,19 +1333,16 @@ Attribute ParseCriticalCSV.VB_Description = "Parses text strings CSV
13741333 OverStringPointer = 1 &
13751334 End If
13761335 End If
1377- FieldsCount = FieldsCount + 1 &
13781336 Loop
13791337 '@----------------------------------------------------------------------------
13801338 'Save the the first record to output array
13811339 HeaderSize = CurrentBufferIndex
1340+ ReDim Preserve buffer(0 To HeaderSize)
13821341 P_MAX_JAGG_INDEX = HeaderSize
13831342 CurrentRecordSize = P_MAX_JAGG_INDEX
13841343 Call CreateJagged (P_CSV_DATA, ImportDepth - 1 &, HeaderSize)
1385- For Counter1 = 0 To HeaderSize
1386- P_CSV_DATA(0 )(Counter1) = buffer(Counter1)
1387- Next Counter1
1344+ P_CSV_DATA(0 ) = buffer()
13881345 Erase buffer
1389- If FieldsAmount = 0 Then FieldsAmount = FieldsCount
13901346 RecordsCount = RecordsCount + 1 &
13911347 '@----------------------------------------------------------------------------
13921348 'Skip lines if needed
@@ -1613,11 +1569,6 @@ ParseCriticalCSV_Error_Handler:
16131569 P_ERROR_DESC = Err.description
16141570 P_ERROR_SOURCE = Err.source
16151571 Exit Sub
1616- ParseCriticalCSV_UnexpectedEnding:
1617- Err.Raise number:=vbObjectError + 9001 , _
1618- source:="CSVinterface Class [ParseCSV_RFC4180]" , _
1619- description:="An unexpected CSV file ending reached."
1620- Resume ParseCriticalCSV_Error_Handler
16211572ParseCriticalCSV_StartingIndexOutOfBound:
16221573 Err.Raise number:=vbObjectError + 9002 , _
16231574 source:="CSVinterface Class [ParseCSV_RFC4180]" , _
@@ -1646,7 +1597,6 @@ Attribute ParseCSV.VB_Description = "Parses text strings CSV
16461597 Dim NextPos As Long
16471598 Dim PrevPos As Long
16481599 Dim Pointer As Long
1649- Dim tmpDelimiter As String
16501600
16511601 On Error GoTo ErrHandler_ParseCS
16521602 '@----------------------------------------------------------------------------
@@ -1804,7 +1754,7 @@ Err_Hnd:
18041754 Resume Exit_Proc
18051755End Function
18061756Public Sub ResetToDefault ()
1807- Attribute ResetToDefault.VB_Description = "Resets the all the options to its default value."
1757+ Attribute ResetToDefault.VB_Description = "Resets all the options to its default value."
18081758 P_COMMENTSTOKEN = AscW("#" )
18091759 P_CONNECTED = False
18101760 P_ENDING_RECORD = 1 &
@@ -1882,7 +1832,6 @@ Attribute TwoDimToJaggedArray.VB_Description = "Deconstructs a 2D string array a
18821832 Dim UBj2 As Long , LBj2 As Long
18831833 Dim MaxDim1 As Long , MaxDim2 As Long
18841834 Dim jgdCounter1 As Long , jgdCounter2 As Long
1885- Dim tmpDimension As Long
18861835 Dim tdimCounter As Long , tdimCounter2 As Long
18871836
18881837 On Error GoTo TwoDimToJaggedArray_Err_Handler
0 commit comments