Skip to content

Commit 1b23247

Browse files
committed
Added error handling to filter function
1 parent 8fa0225 commit 1b23247

File tree

1 file changed

+27
-22
lines changed

1 file changed

+27
-22
lines changed

src/CSVArrayList.cls

Lines changed: 27 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -103,10 +103,10 @@ End Property
103103
''' </summary>
104104
''' <param name="Index">Item's position in this instance.</param>
105105
''' <param name="aValue">The value to overwrite the element.</param>
106-
Public Property Let item(Index As Long, aValue As Variant)
106+
Public Property Let item(Index As Long, AValue As Variant)
107107
Select Case Index
108108
Case 0 To CurrentIndex
109-
Buffer(Index) = aValue
109+
Buffer(Index) = AValue
110110
Case Else
111111
err.Raise 9
112112
End Select
@@ -130,34 +130,34 @@ End Property
130130
''' <summary>
131131
''' Gets or sets the current instance's array.
132132
''' </summary>
133-
Public Property Let items(aValue As Variant)
133+
Public Property Let items(AValue As Variant)
134134
Clear
135-
If IsArray(aValue) Then
135+
If IsArray(AValue) Then
136136
Dim Dim1Pointer As Long
137137
Dim Dim2Pointer As Long
138138
Dim tmpRow() As Variant
139139

140-
If MultiDimensional(aValue) Then '2D array expected
141-
ReDim tmpRow(LBound(aValue, 2) To UBound(aValue, 2))
142-
For Dim1Pointer = LBound(aValue) To UBound(aValue)
143-
For Dim2Pointer = LBound(aValue, 2) To UBound(aValue, 2)
144-
tmpRow(Dim2Pointer) = aValue(Dim1Pointer, Dim2Pointer)
140+
If MultiDimensional(AValue) Then '2D array expected
141+
ReDim tmpRow(LBound(AValue, 2) To UBound(AValue, 2))
142+
For Dim1Pointer = LBound(AValue) To UBound(AValue)
143+
For Dim2Pointer = LBound(AValue, 2) To UBound(AValue, 2)
144+
tmpRow(Dim2Pointer) = AValue(Dim1Pointer, Dim2Pointer)
145145
Next Dim2Pointer
146146
Add tmpRow
147147
Next Dim1Pointer
148148
Else 'Jagged or 1D array expected
149-
If IsJaggedArray(aValue) Then
150-
For Dim1Pointer = LBound(aValue) To UBound(aValue)
151-
Add aValue(Dim1Pointer)
149+
If IsJaggedArray(AValue) Then
150+
For Dim1Pointer = LBound(AValue) To UBound(AValue)
151+
Add AValue(Dim1Pointer)
152152
Next Dim1Pointer
153153
Else
154-
For Dim1Pointer = LBound(aValue) To UBound(aValue)
155-
Add2 aValue
154+
For Dim1Pointer = LBound(AValue) To UBound(AValue)
155+
Add2 AValue
156156
Next Dim1Pointer
157157
End If
158158
End If
159159
Else
160-
Add2 aValue
160+
Add2 AValue
161161
End If
162162
End Property
163163
'////////////////////////////////////////////////////////////////////////////////////////////
@@ -170,16 +170,16 @@ End Property
170170
''' Appends a copy of the specified value to the current instance.
171171
''' </summary>
172172
''' <param name="aValue">The value to append.</param>
173-
Public Sub Add(aValue As Variant)
173+
Public Sub Add(AValue As Variant)
174174
Attribute Add.VB_Description = "Appends a copy of the specified value to the current instance."
175175
CurrentIndex = CurrentIndex + 1
176176
On Error GoTo Expand_Buffer
177-
Buffer(CurrentIndex) = aValue
177+
Buffer(CurrentIndex) = AValue
178178
Exit Sub
179179
Expand_Buffer:
180180
MaxIndex = 2 * (MaxIndex + 1) - 1
181181
ReDim Preserve Buffer(0 To MaxIndex)
182-
Buffer(CurrentIndex) = aValue
182+
Buffer(CurrentIndex) = AValue
183183
End Sub
184184
''' <summary>
185185
''' Appends a copy, in jagged array fashion, of the specified
@@ -350,10 +350,15 @@ Public Function Filter(Pattern As String, startIndex As Long) As CSVArrayList
350350
.Create Pattern
351351
FilterFields() = FieldsToFilter(.CurrentVariables)
352352
For rCounter = startIndex - 1 To CurrentIndex
353+
On Error Resume Next
353354
.Eval FilterVarValues(rCounter, FilterFields)
354355
If .ErrorType = ExpressionErrors.errNone Then
355-
If CBool(.Result) Then
356-
Filter.Add Buffer(rCounter) 'Append current record
356+
If err.Number = 0 Then
357+
If CBool(.Result) Then
358+
Filter.Add Buffer(rCounter) 'Append current record
359+
End If
360+
Else
361+
err.Clear
357362
End If
358363
End If
359364
Next rCounter
@@ -623,14 +628,14 @@ End Sub
623628
''' </summary>
624629
''' <param name="Index">The index into which the Item'll be inserted.</param>
625630
''' <param name="aValue">The value to be inserted.</param>
626-
Public Sub Insert(Index As Long, aValue As Variant)
631+
Public Sub Insert(Index As Long, AValue As Variant)
627632
Attribute Insert.VB_Description = "Inserts an Item, at the given Index, in the current instance of the class."
628633
Dim tmpCopy() As Variant
629634
Dim iCounter As Long
630635

631636
Select Case Index
632637
Case 0 To CurrentIndex + 1 'Avoids to leave empty items
633-
Me.Add aValue
638+
Me.Add AValue
634639
'Checks if the item need to be placed on a previous Index
635640
If Index < CurrentIndex Then
636641
tmpCopy() = Buffer

0 commit comments

Comments
 (0)