Skip to content

Commit 9b76af5

Browse files
authored
Update README.md
1 parent 764fb29 commit 9b76af5

File tree

1 file changed

+288
-0
lines changed

1 file changed

+288
-0
lines changed

README.md

Lines changed: 288 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,294 @@ If you don't know how to get started with VBA-CSV Interface class, visit the [do
2727

2828
Visit the [frequently asked questions section](https://ws-garcia.github.io/VBA-CSV-interface/home/FAQ.html) for the most common questions.
2929

30+
### Using the Code
31+
32+
<p>This section will attempt to analyze all the capabilities of the CSV interface.</p>
33+
34+
<p>Import whole CSV file:</p>
35+
36+
<pre lang="vbscript">
37+
Sub CSVimport()
38+
Dim CSVint As CSVinterface
39+
40+
Set CSVint = New CSVinterface
41+
With CSVint.parseConfig
42+
.path = &quot;C:\Sample.csv&quot; &#39; Full path to the file, including its extension.
43+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
44+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
45+
End With
46+
With csvinf
47+
.ImportFromCSV .parseConfig &#39; Import the CSV to internal object
48+
End With
49+
End Sub</pre>
50+
51+
<p>Now suppose from the file &quot;<em>Sample.csv</em>&quot; the user only requires to import a specific range of records. It is possible to write a code like the one shown below:</p>
52+
53+
<pre lang="vbscript">
54+
Sub CSVimportRecordsRange()
55+
Dim CSVint As CSVinterface
56+
57+
Set CSVint = New CSVinterface
58+
With CSVint.parseConfig
59+
.path = &quot;C:\Sample.csv&quot; &#39; Full path to the file, including its extension.
60+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
61+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
62+
.startingRecord = 10 &#39; Start import on the tenth record
63+
.endingRecord = 20 &#39; End of importation in the 20th record
64+
End With
65+
With csvinf
66+
.ImportFromCSV .parseConfig &#39; Import the CSV to internal object
67+
End With
68+
End Sub</pre>
69+
70+
<p>If the user wants to sort the imported data, a code like the following can be written:</p>
71+
72+
<pre lang="vbscript">
73+
Sub CSVimportAndSort()
74+
Dim CSVint As CSVinterface
75+
76+
Set CSVint = New CSVinterface
77+
With CSVint.parseConfig
78+
.path = &quot;C:\Sample.csv&quot; &#39; Full path to the file, including its extension.
79+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
80+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
81+
End With
82+
With CSVint
83+
.ImportFromCSV .parseConfig &#39; Import the CSV to internal object
84+
.Sort SortColumn:=1, Descending:=True &#39; Sort imported data on first column
85+
End With
86+
End Sub</pre>
87+
88+
<p>CSV data are mainly treated as text strings, what if the user wants to do some calculations on the data obtained from a given file? In this situation, the user can change the behavior of the parser to work in dynamic typing mode. Here&#39;s an example:</p>
89+
90+
<pre lang="vbscript">
91+
Sub CSVimportAndTypeData()
92+
Dim CSVint As CSVinterface
93+
94+
Set CSVint = New CSVinterface
95+
With CSVint.parseConfig
96+
.path = &quot;C:\Sample.csv&quot; &#39; Full path to the file, including its extension.
97+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
98+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
99+
.dynamicTyping = True &#39; Enable dynamic typing mode
100+
&#39;@---------------------------------------------------------
101+
&#39; Configure dynamic typing
102+
.DefineTypingTemplate TypeConversion.ToDate, _
103+
TypeConversion.ToLong, _
104+
TypeConversion.ToDouble
105+
.DefineTypingTemplateLinks 6, _
106+
7, _
107+
10
108+
&#39; The dynamic typing mode will perform the following:
109+
&#39; * Over column 6 ---&gt; String To Date data Type conversion
110+
&#39; * Over column 7 ---&gt; String To Long data Type conversion
111+
&#39; * Over column 10 ---&gt; String To Double data Type conversion
112+
End With
113+
With CSVint
114+
.ImportFromCSV .parseConfig &#39; Import the CSV to internal object
115+
End With
116+
End Sub</pre>
117+
118+
<p>The escape character can be defined as one of them, according to an enumeration:</p>
119+
120+
<pre lang="vbscript">
121+
Sub SetEscapeChar()
122+
Dim CSVint As CSVinterface
123+
124+
Set CSVint = New CSVinterface
125+
With CSVint.parseConfig
126+
.escapeToken = EscapeTokens.DoubleQuotes &#39; 2 = [&quot;] (Default)
127+
&#39;.escapeToken = EscapeTokens.Apostrophe &#39; 1 = [&#39;]
128+
&#39;.escapeToken = EscapeTokens.Tilde &#39; 3 = [~]
129+
End With
130+
End Sub</pre>
131+
132+
<p>Once the data is imported and saved to the internal object, the user can access it in the same way as a standard VBA array. An example would be:</p>
133+
134+
<pre lang="vbscript">
135+
Sub LoopData(ByRef CSVint As CSVinterface)
136+
With CSVint
137+
Dim iCounter As Long
138+
Dim cRecord() As Variant &#39; Records are stored as a one-dimensional array.
139+
Dim cField As Variant
140+
141+
For iCounter = 0 To CSVint.count - 1
142+
cRecord() = .item(iCounter) &#39; Retrieves a record
143+
cField = .item(iCounter, 2) &#39; Retrieves the 2nd field of the current record
144+
Next
145+
End With
146+
End Sub</pre>
147+
148+
<p>However, it is sometimes disadvantageous to store data in containers other than VBA arrays. This becomes especially noticeable when it is required to write the information stored in Excel&#39;s own objects, such as spreadsheets, or VBA user forms, the case of list boxes, which allow to be filled in a single instruction using arrays. Then, the user can copy the information from the internal object using code like this:</p>
149+
150+
<pre lang="vbscript">
151+
Sub DumpData(ByRef CSVint As CSVinterface)
152+
Dim oArray() As Variant
153+
With CSVint
154+
.DumpToArray oArray &#39; Dump the internal data into a two-dimensional array
155+
.DumpToJaggedArray oArray &#39; Dump the internal data into a jagged array
156+
.DumpToSheet &#39; Dump the internal data into a new sheet
157+
&#39; using ThisWorkbook
158+
&#39;@-------------------------------------------------------------------
159+
&#39; *NOTE: ONLY AVAILABLE FOR THE ACCESS VERSION OF THE CSV INTERFACE
160+
&#39; Dump the internal data into the Table1 in oAccessDB database.
161+
&#39; The method would create indexes in the 2nd and 3th fields.
162+
.DumpToAccessTable oAccessDB, _
163+
&quot;Table1&quot;, _
164+
2, 3
165+
End With
166+
End Sub</pre>
167+
168+
<p>So far, in the examples addressed, the user has been allowed to choose between two actions:</p>
169+
170+
<ol>
171+
<li>Import <em>ALL records</em> contained in a CSV file.</li>
172+
<li>Import a <em>recordset</em>, starting at record X and ending at record Y.</li>
173+
</ol>
174+
175+
<p>In both options, the user is obliged to import all fields (columns) present in the file. Most CSV file parsers only offer the first option, but what if the user wants to save only the information that is relevant to them? and what happens is intended to store in memory only the registers that meet a certain set of requirements?</p>
176+
177+
<p>An user may need to import 2 of 12 columns from a CSV file, in this case, the user can use something like:</p>
178+
179+
<pre lang="vbscript">
180+
Sub CSVimportDesiredColumns()
181+
Dim CSVint As CSVinterface
182+
183+
Set CSVint = New CSVinterface
184+
With CSVint.parseConfig
185+
.path = &quot;C:\Sample.csv&quot; &#39; Full path to the file, including its extension.
186+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
187+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
188+
End With
189+
With CSVint
190+
.ImportFromCSV .parseConfig, _
191+
1, &quot;Revenue&quot; &#39; Import 1st and &quot;Revenue&quot; fields ONLY
192+
End With
193+
End Sub</pre>
194+
195+
<p>So, OK, let&#39;s imagine now that an user wants to apply some logic before saving the data, in which case they can step through the records in the CSV file one by one, using the sequential reader, as shown in the following example:</p>
196+
197+
<pre lang="vbscript">
198+
Sub CSVsequentialImport()
199+
Dim CSVint As CSVinterface
200+
Dim csvRecord As ECPArrayList
201+
202+
Set CSVint = New CSVinterface
203+
With CSVint.parseConfig
204+
.path = &quot;C:\Sample.csv&quot; &#39; Full path to the file, including its extension.
205+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
206+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
207+
End With
208+
With CSVint
209+
.OpenSeqReader .parseConfig, _
210+
1, &quot;Revenue&quot; &#39; Import the 1st and &quot;Revenue&quot; fields using
211+
&#39; seq. reader
212+
Do
213+
Set csvRecord = .GetRecord
214+
&#39;//////////////////////////////////////////////
215+
&#39;Implement your logic here
216+
&#39;//////////////////////////////////////////////
217+
Loop While Not csvRecord Is Nothing &#39; Loop until the end of the file is reached
218+
End With
219+
End Sub</pre>
220+
221+
<p>Is there a way to sequentially fetch a set of records at a time instead of a single record? Currently, there is no built-in method to do that with a single instruction, as in the examples above, but with a few extra lines of code and the tools provided by the library, it is possible to achieve that goal. This is illustrated in the following example where the CSV file is streamed:</p>
222+
223+
<pre lang="vbscript">
224+
Sub CSVimportChunks()
225+
Dim CSVint As CSVinterface
226+
Dim StreamReader As ECPTextStream
227+
228+
Set CSVint = New CSVinterface
229+
With CSVint.parseConfig
230+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
231+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
232+
End With
233+
Set StreamReader = New ECPTextStream
234+
With StreamReader
235+
.endStreamOnLineBreak = True &#39; Instruct to find line breaks
236+
.OpenStream &quot;C:\Sample.csv&quot; &#39; Connect to CSV file
237+
Do
238+
.ReadText &#39; Read a CSV chunk
239+
CSVint.ImportFromCSVString .bufferString, _
240+
CSVint.parseConfig, _
241+
1, &quot;Revenue&quot; &#39; Import a set of records
242+
&#39;//////////////////////////////////////
243+
&#39;Implement your logic here
244+
&#39;//////////////////////////////////////
245+
Loop While Not .atEndOfStream &#39; Continue until reach
246+
&#39; the end of the CSV file.
247+
End With
248+
Set CSVint = Nothing
249+
Set StreamReader = Nothing
250+
End Sub</pre>
251+
252+
<p>So far, it has been outlined the way in which you can import the records from a CSV file sequentially, the following example shows how to filter the records, in a like SQL way, according to whether they meet a criterion set by the user:</p>
253+
254+
<pre lang="vbscript">
255+
Sub QueryCSV(path As String, ByVal keyIndex As Long, queryFilters As Variant)
256+
Dim CSVint As CSVinterface
257+
Dim CSVrecords As ECPArrayList
258+
259+
Set CSVint = New CSVinterface
260+
With CSVint.parseConfig
261+
.path = &quot;C:\Sample.csv&quot;
262+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
263+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
264+
End With
265+
If path &lt;&gt; vbNullString Then
266+
&#39;@-----------------------------------------------
267+
&#39; The following instruction will filter the data
268+
&#39; on the keyIndex(th) field.
269+
Set CSVrecords = CSVint.GetCSVsubset(path, _
270+
queryFilters, _
271+
keyIndex)
272+
CSVint.DumpToSheet DataSource:=CSVrecords &#39; Dump result to new WorkSheet
273+
Set CSVint = Nothing
274+
Set CSVrecords = Nothing
275+
End If
276+
End Sub</pre>
277+
278+
<p>In some situations, we may encounter a CSV file with a combination of <code>vbCrLf</code>, <code>vbCr</code> and <code>vbLf</code> as record delimiters. This can happen for many reasons, but the most common is by adding data to an existing CSV file without checking the configuration of the previously stored information. These cases will break the logic of many robust CSV parsers, including the demo of the 737K weekly downloaded <a href="https://www.papaparse.com/demo">Papa Parse</a>. The next example shows how an user can import CSV files with mixed line break as record delimiter, an option that uses the <code>turnStreamRecDelimiterToLF</code> property of the <a href="https://ws-garcia.github.io/VBA-CSV-interface/api/properties/parseconf.html"><code>parseConfig</code></a> object to work with these special CSV files.</p>
279+
280+
<pre lang="vbscript">
281+
Sub ImportMixedLineEndCSV()
282+
Dim CSVint As CSVinterface
283+
284+
Set CSVint = New CSVinterface
285+
With CSVint.parseConfig
286+
.path = &quot;C:\Mixed Line Breaks.csv&quot;
287+
.fieldsDelimiter = &quot;,&quot; &#39; Columns delimiter
288+
.recordsDelimiter = vbCrLf &#39; Rows delimiter
289+
.turnStreamRecDelimiterToLF = True &#39; All delimiters will be turned into vbLf
290+
End With
291+
With CSVint
292+
.ImportFromCSV .parseConfig
293+
End With
294+
Set CSVint = Nothing
295+
End Sub</pre>
296+
297+
<p>In all the above examples, an implicit assumption has been made, and that is that the user knows the configuration of the CSV file to be imported, so the question arises: can it be possible that the user does not know the configuration of the file to be imported? It is certainly possible, so how can the CSV interface help in these cases?</p>
298+
299+
<p>The tool includes a utility to guess field delimiters, record delimiters and escape character. This can be done with code like the following:</p>
300+
301+
<pre lang="vbscript">
302+
Sub DelimitersGuessing()
303+
Dim CSVint As CSVinterface
304+
305+
Set CSVint = New CSVinterface
306+
With CSVint.parseConfig
307+
.path = &quot;C:\Sample.csv&quot; &#39; Full path to the file, including its extension.
308+
End With
309+
With CSVint
310+
.GuessDelimiters .parseConfig &#39; Try to guess delimiters and save to internal
311+
&#39; parser configuration object.
312+
&#39;@--------------------------------------------------------------
313+
&#39; *NOTE: the user can also create a custom configuration object
314+
&#39; and try to guess the delimiter with it.
315+
End With
316+
End Sub</pre>
317+
30318
## Contributing
31319

32320
In order to contribute within this project, please see the [guidance for contributing](https://ws-garcia.github.io/VBA-CSV-interface/contributing.html).

0 commit comments

Comments
 (0)