Skip to content

Commit 7493b32

Browse files
authored
Update CSVfileManager.cls
1 parent c1a2de0 commit 7493b32

File tree

1 file changed

+33
-41
lines changed

1 file changed

+33
-41
lines changed

src/CSVfileManager.cls

Lines changed: 33 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -84,13 +84,13 @@ Private Const CHR_SPACE As String = " "
8484
'#
8585
'////////////////////////////////////////////////////////////////////////////////////////////
8686
' PROPERTIES VARIABLES:
87-
Private P_COERCE_TYPE As CoerceTypes '-----------Holds the char used for coerce the fields
8887
Private P_CONNECTED As Boolean '-----------------Holds the connection state
8988
Private P_CSV_DATA() As String '-----------------Holds the CSV data for current instance
9089
Private P_ENDING_RECORD As Long '----------------Pointer to the last record to be imported
9190
Private P_ERROR_DESC As String '-----------------Holds the Error Description
9291
Private P_ERROR_NUMBER As Long '-----------------Holds the Error number
9392
Private P_ERROR_SOURCE As String '---------------Holds the Error source
93+
Private P_ESCAPE_CHAR As EscapeType '------------Holds the char used for escape fields
9494
Private P_FIELDS_DELIMITER As String '-----------Holds the current delimiter for CSV fields
9595
Private P_FILENAME As String '-------------------Holds the actual file name
9696
Private P_RECORDS_DELIMITER As String '----------Holds the records delimiter (CR, LF or CRLF)
@@ -101,9 +101,9 @@ Private P_SUCCESSFUL_IMPORT As Boolean
101101
'#
102102
'////////////////////////////////////////////////////////////////////////////////////////////
103103
' ENUMERATIONS:
104-
Public Enum CoerceTypes
104+
Public Enum EscapeType
105105
DoubleQuotes = 2
106-
NotCoerce = 0
106+
NotEscape = 0
107107
Apostrophe = 1
108108
End Enum
109109
'////////////////////////////////////////////////////////////////////////////////////////////
@@ -121,11 +121,11 @@ Private FileHandled As Integer '-------Pointer to the actual CSV file
121121
'////////////////////////////////////////////////////////////////////////////////////////////
122122
' PROPERTIES:
123123
'#
124-
Public Property Get CoerceType() As CoerceTypes
125-
CoerceType = P_COERCE_TYPE
124+
Public Property Get EscapeChar() As EscapeType
125+
EscapeChar = P_ESCAPE_CHAR
126126
End Property
127-
Public Property Let CoerceType(ByVal Coerce As CoerceTypes)
128-
P_COERCE_TYPE = Coerce
127+
Public Property Let EscapeChar(ByVal EscapeChr As EscapeType)
128+
P_ESCAPE_CHAR = EscapeChr
129129
End Property
130130
Public Property Get Connected() As Boolean
131131
Connected = P_CONNECTED
@@ -150,7 +150,7 @@ Public Property Let EndingRecord(ByVal RecNumber As Long)
150150
Case Is >= 1&
151151
P_ENDING_RECORD = RecNumber - 1
152152
Case Else
153-
P_ENDING_RECORD = 0& 'Set the pointer to the last available record in the CSV file
153+
P_ENDING_RECORD = 0&
154154
End Select
155155
End Property
156156
Public Property Get ErrDescription() As String
@@ -224,7 +224,7 @@ Public Property Let StartingRecord(ByVal RecNumber As Long)
224224
Case Is >= 1&
225225
P_STARTING_RECORD = RecNumber - 1
226226
Case Else
227-
P_STARTING_RECORD = 0& 'Set the pointer to the first available record in the CSV file
227+
P_STARTING_RECORD = 0&
228228
End Select
229229
End Property
230230
'////////////////////////////////////////////////////////////////////////////////////////////
@@ -257,7 +257,6 @@ Private Function CSVcolumns(csvArray() As String, _
257257
' CSVArray. The function requires an one dimentional array with all the CSV records on it.
258258
' Its returns -1 when an error occurs.
259259
'////////////////////////////////////////////////////////////////////////////////////////////
260-
' @Compute columns procedure
261260
Dim iCounter As Long
262261
Dim LB As Long, UB As Long
263262
Dim lngPos As Long
@@ -286,7 +285,7 @@ Public Sub ExportToCSV(csvArray As Variant)
286285
' DESCRIPTION:
287286
' This method export a given VBA array to the location and with the name used in the
288287
' OpenConnection method call. In addition, it uses the CHR_COMMA, and the
289-
' P_COERCE_TYPE that the user's previously defined.
288+
' P_ESCAPE_CHAR that the user's previously defined.
290289
'////////////////////////////////////////////////////////////////////////////////////////////
291290
On Error GoTo ErrHandler_ExportToCSV
292291
DoEvents
@@ -333,11 +332,9 @@ Public Function ImportFromCSV(Optional HeadersOmission As Boolean = False) As CS
333332
' DESCRIPTION:
334333
' This method import CSV content to a VBA array. The file to be imported has the name used
335334
' in the OpenConnection method call. In addition, it uses the CHR_COMMA, and the
336-
' P_COERCE_TYPE that the user's previously defined. The optional parameter HeadersOmission
335+
' P_ESCAPE_CHAR that the user's previously defined. The optional parameter HeadersOmission
337336
' allows user avoid importation of fields titles (1st line).
338337
'////////////////////////////////////////////////////////////////////////////////////////////
339-
' @Import procedure
340-
341338
On Error GoTo ErrHandler_ImportFromCSV
342339
DoEvents
343340
If P_CONNECTED Then
@@ -377,20 +374,19 @@ Private Function JoinRecordsFields(RecordsArray As Variant) As String
377374
' DESCRIPTION:
378375
' This method returns a string that contains the concatenation of each records on the
379376
' RecordsArray variable. All the fields are joined using the especified CHR_COMMA
380-
' and P_COERCE_TYPE variables.
377+
' and P_ESCAPE_CHAR variables.
381378
'#
382379
' INPUT:
383380
' RecordsArray {A = [|a| |b| |c| : |d| |e| |f|]}
384381
'#
385382
' OUTPUTS:
386383
' @comma as Deimiter:
387-
' [a[P_COERCE_TYPE],[P_COERCE_TYPE]b[P_COERCE_TYPE],[P_COERCE_TYPE]c [P_RECORDS_DELIMITER]
388-
' d[P_COERCE_TYPE],[P_COERCE_TYPE]e[P_COERCE_TYPE],[P_COERCE_TYPE]f]
384+
' [a[P_ESCAPE_CHAR],[P_ESCAPE_CHAR]b[P_ESCAPE_CHAR],[P_ESCAPE_CHAR]c [P_RECORDS_DELIMITER]
385+
' d[P_ESCAPE_CHAR],[P_ESCAPE_CHAR]e[P_ESCAPE_CHAR],[P_ESCAPE_CHAR]f]
389386
' @SemiColom as Deimiter:
390-
' [a[P_COERCE_TYPE];[P_COERCE_TYPE]b[P_COERCE_TYPE];[P_COERCE_TYPE]c [P_RECORDS_DELIMITER]
391-
' d[P_COERCE_TYPE];[P_COERCE_TYPE]e[P_COERCE_TYPE];[P_COERCE_TYPE]f]
387+
' [a[P_ESCAPE_CHAR];[P_ESCAPE_CHAR]b[P_ESCAPE_CHAR];[P_ESCAPE_CHAR]c [P_RECORDS_DELIMITER]
388+
' d[P_ESCAPE_CHAR];[P_ESCAPE_CHAR]e[P_ESCAPE_CHAR];[P_ESCAPE_CHAR]f]
392389
'////////////////////////////////////////////////////////////////////////////////////////////
393-
' @Join records fields proceure
394390
Dim Buffer() As String
395391
Dim CoerceChr As String
396392
Dim ConcatenatedArray() As String
@@ -407,30 +403,30 @@ Private Function JoinRecordsFields(RecordsArray As Variant) As String
407403
ub2 = UBound(RecordsArray, 2)
408404
'@----------------------------------------------------------------------------
409405
'Set Data and coerce Delimiter
410-
Select Case P_COERCE_TYPE
411-
Case 0 'Fields delimited with P_FIELDS_DELIMITER
406+
Select Case P_ESCAPE_CHAR
407+
Case 0
412408
DataDelimiter = P_FIELDS_DELIMITER
413409
CoerceChr = vbNullString
414-
Case 1 'Fields delimited with Apostrophe
410+
Case 1
415411
DataDelimiter = CHR_APOSTROPHE & P_FIELDS_DELIMITER & CHR_APOSTROPHE
416412
CoerceChr = CHR_APOSTROPHE
417-
Case Else 'Fields delimited with Double Quotes
413+
Case Else
418414
DataDelimiter = CHR_DOUBLE_QUOTES & P_FIELDS_DELIMITER & CHR_DOUBLE_QUOTES
419415
CoerceChr = CHR_DOUBLE_QUOTES
420416
End Select
421417
'@----------------------------------------------------------------------------
422418
'Set the char buffer
423419
JoinBuffer(0) = CoerceChr
424-
JoinBuffer(1) = vbNullString 'Store the value to be coerced here
420+
JoinBuffer(1) = vbNullString
425421
JoinBuffer(2) = CoerceChr
426422
'@----------------------------------------------------------------------------
427423
'Set array sizes
428-
ReDim ConcatenatedArray(LB1 To UB1) 'Resize the output array
424+
ReDim ConcatenatedArray(LB1 To UB1)
429425
ReDim Buffer(LB2 To ub2)
430426
'@----------------------------------------------------------------------------
431427
'Concatenate fields
432-
For iLCounter = LB1 To UB1 'Loop trhrought all rows
433-
For jLCounter = LB2 To ub2 'Loop trhrought all columns
428+
For iLCounter = LB1 To UB1
429+
For jLCounter = LB2 To ub2
434430
Buffer(jLCounter) = RecordsArray(iLCounter, jLCounter)
435431
Next jLCounter
436432
JoinBuffer(1) = Join$(Buffer, DataDelimiter)
@@ -459,7 +455,7 @@ Private Function MultiDimensional(CheckArray As Variant) As Boolean
459455
On Error GoTo ErrHandler_MultiDimensional
460456

461457
If UBound(CheckArray, 2) > 0 Then
462-
MultiDimensional = True 'more than 1 dimension
458+
MultiDimensional = True
463459
End If
464460
Exit Function
465461
ErrHandler_MultiDimensional:
@@ -529,7 +525,7 @@ Public Sub ParseCSV(ByRef csvText As String, _
529525
Dim lRows As Long
530526
Dim mCounter As Long
531527
Dim NextPos As Long
532-
Dim ParseOption As CoerceTypes
528+
Dim ParseOption As EscapeType
533529
Dim PrevPos As Long
534530
Dim Pointer As Long
535531
Dim sSplit() As String
@@ -540,16 +536,16 @@ Public Sub ParseCSV(ByRef csvText As String, _
540536
Erase P_CSV_DATA
541537
'@----------------------------------------------------------------------------
542538
'Set Coerce Type to records and fields
543-
Select Case P_COERCE_TYPE
544-
Case 0 'Not corce
539+
Select Case P_ESCAPE_CHAR
540+
Case 0
545541
DataDelimiter = P_FIELDS_DELIMITER
546542
LinesDelimiter = P_RECORDS_DELIMITER
547543
ParseOption = 0
548-
Case 1 'Fields delimited with Apostrophe
544+
Case 1
549545
DataDelimiter = CHR_APOSTROPHE & P_FIELDS_DELIMITER & CHR_APOSTROPHE
550546
LinesDelimiter = CHR_APOSTROPHE & P_RECORDS_DELIMITER & CHR_APOSTROPHE
551547
ParseOption = 1
552-
Case Else 'Fields delimited with Double Quotes
548+
Case Else
553549
DataDelimiter = CHR_DOUBLE_QUOTES & P_FIELDS_DELIMITER & CHR_DOUBLE_QUOTES
554550
LinesDelimiter = CHR_DOUBLE_QUOTES & P_RECORDS_DELIMITER & CHR_DOUBLE_QUOTES
555551
ParseOption = 2
@@ -569,9 +565,7 @@ Public Sub ParseCSV(ByRef csvText As String, _
569565
'@----------------------------------------------------------------------------
570566
'Ommit the coerce char from the upper and lower elements
571567
If ParseOption <> 0 Then
572-
'First char omission
573568
csvArray(ArrayLB) = MidB$(csvArray(ArrayLB), 3)
574-
'Omit the last last char and VbCrLf if needed
575569
If RightB$(csvArray(ArrayUB), 4) = vbCrLf Then
576570
csvArray(ArrayUB) = MidB$(csvArray(ArrayUB), 1, LenB(csvArray(ArrayUB)) - 6)
577571
Else
@@ -583,7 +577,7 @@ Public Sub ParseCSV(ByRef csvText As String, _
583577
Select Case P_STARTING_RECORD
584578
Case 0&
585579
lngLB = ArrayLB
586-
Case Is > ArrayUB 'Out of bound
580+
Case Is > ArrayUB
587581
lngLB = ArrayUB
588582
Case Else
589583
lngLB = P_STARTING_RECORD
@@ -619,9 +613,8 @@ Public Sub ParseCSV(ByRef csvText As String, _
619613
'Process the data
620614
Pointer = hPos
621615
Do While lCounter <= lngUB
622-
mCounter = 0 'Column counter
616+
mCounter = 0
623617
PrevPos = 1
624-
'Next position of the pointer over the record
625618
NextPos = CLng(InStrB(PrevPos, csvArray(lCounter), _
626619
DataDelimiter))
627620
Do While NextPos
@@ -645,8 +638,7 @@ ErrHandler_ParseCS:
645638
Erase P_CSV_DATA
646639
End Sub
647640
Public Sub ResetToDefault()
648-
'Reset the defaults values
649-
P_COERCE_TYPE = 0
641+
P_ESCAPE_CHAR = 0
650642
P_CONNECTED = False
651643
P_ENDING_RECORD = 0&
652644
P_ERROR_DESC = vbNullString

0 commit comments

Comments
 (0)