Skip to content

Commit 5bebdd2

Browse files
authored
Export method optimization
1 parent 79b4754 commit 5bebdd2

File tree

1 file changed

+22
-33
lines changed

1 file changed

+22
-33
lines changed

src/CSVfileManager.cls

Lines changed: 22 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ Attribute VB_PredeclaredId = False
99
Attribute VB_Exposed = False
1010
'#
1111
'////////////////////////////////////////////////////////////////////////////////////////////
12-
' Copyright © 2020 W. García
12+
' Copyright © 2020 W. García
1313
' GPL-3.0 license | https://github.com/ws-garcia/VBA-CSV-fileManager
1414
' https://ingwilfredogarcia.wordpress.com
1515
'#
@@ -29,8 +29,8 @@ Attribute VB_Exposed = False
2929
' This class is inspired in a work available in
3030
' https://www.freevbcode.com/ShowCode.asp?ID=3110
3131
' The class module was designed and tested using
32-
' Windows 7® and is supose to work as well over
33-
' more recent Microsoft™ operative system.
32+
' Windows 7® and is supose to work as well over
33+
' more recent Microsoft™ operative system.
3434
'#
3535
' Use CSVfileManager class to simplify the work
3636
' with comma separated value (CSV) files. It allow
@@ -259,21 +259,19 @@ Private Function CSVcolumns(csvArray() As String, _
259259
'////////////////////////////////////////////////////////////////////////////////////////////
260260
' @Compute columns procedure
261261
Dim iCounter As Long
262-
Dim LB As Long, UB As Long '-------Arraybounds
262+
Dim LB As Long, UB As Long
263263
Dim lngPos As Long
264-
Dim MDCounter As Long '------------Store csvDelimiter matches
264+
Dim MDCounter As Long
265265
Dim NumOfDelimiter As Long
266266

267267
On Error GoTo ErrHandler_CSVcolumns
268268
LB = LBound(csvArray)
269269
UB = UBound(csvArray)
270270
NumOfDelimiter = 0
271271
MDCounter = 0
272-
'lngPos = CLng(InStr(1, csvArray(LB), FieldsDelimiter))
273272
lngPos = CLng(InStrB(csvArray(LB), FieldsDelimiter))
274273
Do While lngPos
275274
MDCounter = MDCounter + 1
276-
'lngPos = CLng(InStr(lngPos + 1, csvArray(LB), FieldsDelimiter))
277275
lngPos = CLng(InStrB(lngPos + 2, csvArray(LB), FieldsDelimiter))
278276
Loop
279277
NumOfDelimiter = MDCounter
@@ -294,12 +292,8 @@ Public Sub ExportToCSV(csvArray As Variant)
294292
DoEvents
295293
If P_CONNECTED Then
296294
'@----------------------------------------------------------------------------
297-
'Join all the records
298-
FileContent = JoinRecordsFields(csvArray)
299-
'@----------------------------------------------------------------------------
300-
'open the file for binary access
301-
'Write the data on the current opened file
302-
Put #FileHandled, , FileContent
295+
'Join all the records and write the data on the current opened file
296+
Put #FileHandled, , JoinRecordsFields(csvArray)
303297
Call CloseConnection
304298
'@----------------------------------------------------------------------------
305299
P_SUCCESSFUL_EXPORT = True
@@ -341,7 +335,6 @@ Public Function ImportFromCSV(Optional HeadersOmission As Boolean = False) As CS
341335
' in the OpenConnection method call. In addition, it uses the CHR_COMMA, and the
342336
' P_COERCE_TYPE that the user's previously defined. The optional parameter HeadersOmission
343337
' allows user avoid importation of fields titles (1st line).
344-
' The method returns Null when an error occurs.
345338
'////////////////////////////////////////////////////////////////////////////////////////////
346339
' @Import procedure
347340

@@ -486,11 +479,8 @@ Public Sub OpenConnection(csvPathAndFilename As String)
486479
If CLng(InStrB(csvPathAndFilename, ".csv")) = 0 Then
487480
csvPathAndFilename = csvPathAndFilename & ".csv"
488481
Else
489-
'While (Len(csvPathAndFilename) - _
490-
CLng(InStr(csvPathAndFilename, ".csv"))) > 3
491482
While (LenB(csvPathAndFilename) - _
492483
CLng(InStrB(csvPathAndFilename, ".csv"))) > 7
493-
'csvPathAndFilename = Left$(csvPathAndFilename, Len(csvPathAndFilename) - 1)
494484
csvPathAndFilename = LeftB$(csvPathAndFilename, LenB(csvPathAndFilename) - 2)
495485
Wend
496486
End If
@@ -530,7 +520,7 @@ Public Sub ParseCSV(ByRef csvText As String, _
530520
Dim ArrayLB As Long
531521
Dim ArrayUB As Long
532522
Dim csvArray() As String
533-
Dim hPos As Long '-----------------Make the function able to skip the header
523+
Dim hPos As Long
534524
Dim brCounter As Long
535525
Dim lColumns As Long
536526
Dim lCounter As Long
@@ -539,9 +529,9 @@ Public Sub ParseCSV(ByRef csvText As String, _
539529
Dim lRows As Long
540530
Dim mCounter As Long
541531
Dim NextPos As Long
542-
Dim ParseOption As CoerceTypes '---For distinguish between quotes used on records fields
532+
Dim ParseOption As CoerceTypes
543533
Dim PrevPos As Long
544-
Dim Pointer As Long '--------------Point to the current P_CSV_DATA() element
534+
Dim Pointer As Long
545535
Dim sSplit() As String
546536
Dim tmpDelimiter As String
547537

@@ -591,43 +581,43 @@ Public Sub ParseCSV(ByRef csvText As String, _
591581
'@----------------------------------------------------------------------------
592582
'Check if user want Import all records
593583
Select Case P_STARTING_RECORD
594-
Case 0& 'The import will starts in the first record
584+
Case 0&
595585
lngLB = ArrayLB
596586
Case Is > ArrayUB 'Out of bound
597587
lngLB = ArrayUB
598-
Case Else 'Start imports on user's defined record
588+
Case Else
599589
lngLB = P_STARTING_RECORD
600590
End Select
601591
Select Case P_ENDING_RECORD
602-
Case 0& 'Fit Upper bound
592+
Case 0& '
603593
lngUB = ArrayUB
604-
Case Is < lngLB 'Fit Upper bound
594+
Case Is < lngLB
605595
lngUB = ArrayUB
606-
Case Is = lngLB 'lngUB nedd to be at least lngLB
596+
Case Is = lngLB
607597
lngUB = lngLB
608-
Case Is > ArrayUB 'Fit Upper bound
598+
Case Is > ArrayUB
609599
lngUB = ArrayUB
610600
Case Else
611601
lngUB = P_ENDING_RECORD
612602
End Select
613603
'@----------------------------------------------------------------------------
614604
'Take care of headers
615-
If lngLB = ArrayLB Then 'Only the first record can be omitted
616-
If lngUB - lngLB > 0 Then 'Two or more records required
605+
If lngLB = ArrayLB Then
606+
If lngUB - lngLB > 0 Then
617607
If Not HeadersOmission Then
618608
hPos = 0
619609
Else
620610
hPos = 1
621611
End If
622612
End If
623613
End If
624-
lRows = lngUB - lngLB 'Rows required BASE 0
625-
lColumns = CSVcolumns(csvArray, DataDelimiter) - 1 'Columns required BASE 0
614+
lRows = lngUB - lngLB
615+
lColumns = CSVcolumns(csvArray, DataDelimiter) - 1
626616
lCounter = lngLB + hPos
627-
ReDim P_CSV_DATA(0 To lRows - hPos, 0 To lColumns) 'Resize the output
617+
ReDim P_CSV_DATA(0 To lRows - hPos, 0 To lColumns)
628618
'@----------------------------------------------------------------------------
629619
'Process the data
630-
Pointer = hPos 'Point to the position for save the first record
620+
Pointer = hPos
631621
Do While lCounter <= lngUB
632622
mCounter = 0 'Column counter
633623
PrevPos = 1
@@ -641,7 +631,6 @@ Public Sub ParseCSV(ByRef csvText As String, _
641631
mCounter = mCounter + 1
642632
NextPos = CLng(InStrB(PrevPos, csvArray(lCounter), DataDelimiter))
643633
Loop
644-
'Handle the last field for the record
645634
P_CSV_DATA(Pointer - hPos, mCounter) = MidB$(csvArray(lCounter), PrevPos)
646635
lCounter = lCounter + 1
647636
Pointer = Pointer + 1

0 commit comments

Comments
 (0)