Skip to content

Commit cac7420

Browse files
committed
Improvements: integration with VBAexpressions core modules.
The library now has the most powerful VBA filtering capabilities. The user can define complex filtering criteria to retrieve only the fields of relevance.
1 parent f9b0b10 commit cac7420

File tree

9 files changed

+3548
-484
lines changed

9 files changed

+3548
-484
lines changed

src/CSVArrayList.cls

Lines changed: 242 additions & 123 deletions
Large diffs are not rendered by default.

src/CSVSniffer.cls

Lines changed: 118 additions & 118 deletions
Large diffs are not rendered by default.

src/CSVTextStream.cls

Lines changed: 21 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -94,8 +94,8 @@ Public Property Get bufferSize() As Single
9494
Attribute bufferSize.VB_Description = "Gets or sets the buffer’s size, in MB, for text stream operations."
9595
bufferSize = P_BUFFERSIZE
9696
End Property
97-
Public Property Let bufferSize(Value As Single)
98-
P_BUFFERSIZE = Value
97+
Public Property Let bufferSize(value As Single)
98+
P_BUFFERSIZE = value
9999
P_BUFFERLENGTH = CLng(P_BUFFERSIZE * SizeFactor)
100100
Buffer = SPACE$(P_BUFFERLENGTH)
101101
End Property
@@ -114,8 +114,8 @@ Public Property Get endStreamOnLineBreak() As Boolean
114114
Attribute endStreamOnLineBreak.VB_Description = "Allows to end buffer just after the first, from right to left, line break character."
115115
endStreamOnLineBreak = P_ENDSTREAMONLINEBREAK
116116
End Property
117-
Public Property Let endStreamOnLineBreak(Value As Boolean)
118-
P_ENDSTREAMONLINEBREAK = Value
117+
Public Property Let endStreamOnLineBreak(value As Boolean)
118+
P_ENDSTREAMONLINEBREAK = value
119119
End Property
120120
Public Property Get isOpenStream() As Boolean
121121
isOpenStream = P_ISOPENSTREAM
@@ -127,8 +127,8 @@ End Property
127127
Public Property Get linebreakMatchingBehavior() As EndLineMatchingBehavior
128128
linebreakMatchingBehavior = P_LINEBREAKMATCHINGBEHAVIOR
129129
End Property
130-
Public Property Let linebreakMatchingBehavior(Value As EndLineMatchingBehavior)
131-
P_LINEBREAKMATCHINGBEHAVIOR = Value
130+
Public Property Let linebreakMatchingBehavior(value As EndLineMatchingBehavior)
131+
P_LINEBREAKMATCHINGBEHAVIOR = value
132132
End Property
133133
Public Property Get pointerPosition() As Long
134134
Attribute pointerPosition.VB_Description = "Gets the overall pointer position over the current text file."
@@ -146,15 +146,15 @@ Public Property Get unifiedLFOutput() As Boolean
146146
Attribute unifiedLFOutput.VB_Description = "Determines whether the buffer string is returned using only the LF character as a line feed. Similarly, this property instruct to write files without the Unicode Byte Order Mark."
147147
unifiedLFOutput = P_UNIFIEDLFOUTPUT
148148
End Property
149-
Public Property Let unifiedLFOutput(Value As Boolean)
150-
P_UNIFIEDLFOUTPUT = Value
149+
Public Property Let unifiedLFOutput(value As Boolean)
150+
P_UNIFIEDLFOUTPUT = value
151151
End Property
152152
Public Property Get utf8EncodedFile() As Boolean
153153
Attribute utf8EncodedFile.VB_Description = "Indicates whether the buffer string is returned as a decoded string, assuming the file is UTF8 encoded."
154154
utf8EncodedFile = P_UTF8ENCODED
155155
End Property
156-
Public Property Let utf8EncodedFile(Value As Boolean)
157-
P_UTF8ENCODED = Value
156+
Public Property Let utf8EncodedFile(value As Boolean)
157+
P_UTF8ENCODED = value
158158
End Property
159159
'////////////////////////////////////////////////////////////////////////////////////////////
160160
'#
@@ -269,10 +269,10 @@ Private Sub NormalizeLineBreaks()
269269
Loop
270270
P_LINEBREAK = vbLf
271271
End Sub
272-
Public Sub OpenStream(filePath As String)
272+
Public Sub OpenStream(FilePath As String)
273273
Attribute OpenStream.VB_Description = "Opens a stream over a text file."
274274
FileHandled = FreeFile
275-
Open filePath For Binary As #FileHandled
275+
Open FilePath For Binary As #FileHandled
276276
P_ISOPENSTREAM = True
277277
P_STREAMLENGTH = LOF(FileHandled)
278278
StartVariables
@@ -338,28 +338,28 @@ Private Sub StartVariables()
338338
P_ATENDOFSTREAM = False
339339
End Sub
340340
Public Function UTF8Decode(ByVal sStr As String) As String
341-
Dim L As Long, sUTF8 As CSVArrayList, iChar As Long, iChar2 As Long
341+
Dim l As Long, sUTF8 As CSVArrayList, iChar As Long, iChar2 As Long
342342

343343
On Error GoTo UTF8_Decode_error
344344
Set sUTF8 = New CSVArrayList
345-
For L = 1 To LenB(sStr) Step 2
346-
iChar = Asc(MidB$(sStr, L, 2))
345+
For l = 1 To LenB(sStr) Step 2
346+
iChar = Asc(MidB$(sStr, l, 2))
347347
If iChar > 127 Then
348348
If Not iChar And 32 Then ' 2 chars
349-
iChar2 = Asc(MidB$(sStr, L + 2, 2))
349+
iChar2 = Asc(MidB$(sStr, l + 2, 2))
350350
sUTF8.Add ChrW$(((31 And iChar) * 64 + (63 And iChar2)))
351-
L = L + 2
351+
l = l + 2
352352
Else
353353
Dim iChar3 As Integer
354-
iChar2 = Asc(MidB$(sStr, L + 2, 2))
355-
iChar3 = Asc(MidB$(sStr, L + 4, 2))
354+
iChar2 = Asc(MidB$(sStr, l + 2, 2))
355+
iChar3 = Asc(MidB$(sStr, l + 4, 2))
356356
sUTF8.Add ChrW$(((iChar And 15) * 16 * 256) + ((iChar2 And 63) * 64) + (iChar3 And 63))
357-
L = L + 4
357+
l = l + 4
358358
End If
359359
Else
360360
sUTF8.Add ChrW$(iChar)
361361
End If
362-
Next L
362+
Next l
363363
UTF8Decode = Join$(sUTF8.items, vbNullString)
364364
Set sUTF8 = Nothing
365365
Exit Function

src/CSVcallBack.cls

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,40 @@
1+
VERSION 1.0 CLASS
2+
BEGIN
3+
MultiUse = -1 'True
4+
END
5+
Attribute VB_Name = "CSVcallBack"
6+
Attribute VB_GlobalNameSpace = False
7+
Attribute VB_Creatable = False
8+
Attribute VB_PredeclaredId = False
9+
Attribute VB_Exposed = False
10+
Option Explicit
11+
'#
12+
'////////////////////////////////////////////////////////////////////////////////////////////
13+
' Copyright © 2022 W. García
14+
' GPL-3.0 license | https://www.gnu.org/licenses/gpl-3.0.html/
15+
' https://ingwilfredogarcia.wordpress.com
16+
'////////////////////////////////////////////////////////////////////////////////////////////
17+
'#
18+
' GENERAL INFO:
19+
' Class module developed to provide a way to extend the VBAexpression.cls and allow methods
20+
' call back for user defined functions. See: https://stackoverflow.com/a/48372415
21+
'
22+
' Users can register custom modules to expose and use their functions for throght the
23+
' CSVcallBack.cls module. All UDFs must have a single Variant argument that will receive a
24+
' one-dimensional array of strings (one element for each function argument).
25+
'
26+
' For example, if the functions to be used are in a class module called CSVudFunctions.cls, the
27+
' line ['Public UserDefFunctions As New CSVudFunctions'] will be sufficient to expose all its
28+
' internal functions.
29+
'
30+
' After doing this, the user must "bind" a procedure to the desired methods through the
31+
' DeclareUDF method of the VBAexpression.cls:
32+
'
33+
' DeclareUDF UDFname, UDFlib
34+
'
35+
' In the above expression, the UDFname parameter can be an array of function names or a
36+
' string function name. The UDFlib is a string with the name of the class module to be linked.
37+
'////////////////////////////////////////////////////////////////////////////////////////////
38+
'@--------------------------------------------------------------------
39+
' Expose functions defined in the CSVudFunctions.cls
40+
Public UserDefFunctions As New CSVudFunctions

src/CSVdialect.cls

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,8 +60,8 @@ End Enum
6060
Public Property Get escapeMode() As EscapeStyle
6161
escapeMode = P_ESCAPEMODE
6262
End Property
63-
Public Property Let escapeMode(Value As EscapeStyle)
64-
P_ESCAPEMODE = Value
63+
Public Property Let escapeMode(value As EscapeStyle)
64+
P_ESCAPEMODE = value
6565
End Property
6666
''' <summary>
6767
''' Gets or sets the quote token.

0 commit comments

Comments
 (0)