Skip to content

Commit ea2a7be

Browse files
committed
Bug fixed
Indexing bug
1 parent cf8f985 commit ea2a7be

File tree

1 file changed

+58
-56
lines changed

1 file changed

+58
-56
lines changed

src/CSVArrayList.cls

Lines changed: 58 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -323,7 +323,7 @@ Attribute Add2.VB_Description = "Appends a copy, in jagged array fashion, of the
323323
Add2 tmpValue
324324
Next j
325325
Else
326-
If IsJaggedArray(aValues(i)) Then
326+
If isJaggedArray(aValues(i)) Then
327327
For j = LBound(aValues(i)) To UBound(aValues(i))
328328
Add2 aValues(i)(j)
329329
Next j
@@ -386,6 +386,8 @@ Public Sub AddIndexedItem(Key As String, iValue As Variant, _
386386
ReDim Preserve IndexedBuffer(0 To IndexedMaxIndex)
387387
End If
388388
If Not P_KEYS_TREE Then
389+
tmpItem.itemKey = Key
390+
tmpItem.ItemValue = iValue
389391
IndexedBuffer(tmpIdx) = tmpItem
390392
Else
391393
IndexedBuffer(tmpIdx).itemKey = Key
@@ -726,9 +728,9 @@ Public Function Filter(Pattern As String, startIndex As Long, _
726728
On Error Resume Next
727729
.Eval
728730
End If
729-
If .errorType = ExpressionErrors.errNone Then
731+
If .ErrorType = ExpressionErrors.errNone Then
730732
If err.Number = 0 Then
731-
If CBool(.Result) Then
733+
If CBool(.result) Then
732734
If Not Exclude Then
733735
Filter.Add Buffer(rCounter) 'Append current record
734736
End If
@@ -931,7 +933,7 @@ Attribute Concat.VB_Description = "Concatenates the values from the current inst
931933
Add tmpRow
932934
Next Dim1Pointer
933935
Else 'Jagged or 1D array expected
934-
If IsJaggedArray(tmpValues) Then
936+
If isJaggedArray(tmpValues) Then
935937
For Dim1Pointer = LBound(tmpValues) To UBound(tmpValues)
936938
Add tmpValues(Dim1Pointer)
937939
Next Dim1Pointer
@@ -1356,19 +1358,19 @@ End Sub
13561358
''' Returns True if the paseed argument is a jagged array.
13571359
''' </summary>
13581360
''' <param name="Arr">The array to check.</param>
1359-
Public Function IsJaggedArray(arr As Variant) As Boolean
1360-
Attribute IsJaggedArray.VB_Description = "Returns True if the paseed argument is a jagged array."
1361+
Public Function isJaggedArray(arr As Variant) As Boolean
1362+
Attribute isJaggedArray.VB_Description = "Returns True if the paseed argument is a jagged array."
13611363
On Error GoTo IsJaggedArray_Err_Handler
13621364
If IsArray(arr) Then
13631365
If Not MultiDimensional(arr) Then
13641366
Dim BoundingTest As Long
13651367
BoundingTest = LBound(arr(LBound(arr)))
1366-
IsJaggedArray = True
1368+
isJaggedArray = True
13671369
End If
13681370
End If
13691371
Exit Function
13701372
IsJaggedArray_Err_Handler:
1371-
IsJaggedArray = False
1373+
isJaggedArray = False
13721374
End Function
13731375

13741376
Private Function Is2Darray(arr As Variant) As Boolean
@@ -1406,19 +1408,19 @@ Public Function InsertField(aIndex As Long, _
14061408
Dim Evaluator As CSVexpressions
14071409
Dim evalWithOutVar As Boolean
14081410
Dim fCounter As Long
1409-
Dim fldCount As Long
1411+
Dim FldCount As Long
14101412
Dim rCounter As Long
14111413
Dim TargetFields() As Long
14121414

1413-
fldCount = UBound(Buffer(0))
1415+
FldCount = UBound(Buffer(0))
14141416
'@--------------------------------------------------------------------------------
14151417
'Reserve storage
1416-
ReDim cpRecord(0 To fldCount + 1)
1418+
ReDim cpRecord(0 To FldCount + 1)
14171419
cpRecordBK() = cpRecord
14181420
Set Evaluator = New CSVexpressions
14191421
If Formula <> vbNullString Then
14201422
With Evaluator
1421-
.formatResult = True
1423+
.FormatResult = True
14221424
.Create SwitchUnderscoresAndSpaces(Formula, Buffer(0))
14231425
evalWithOutVar = (.CurrentVariables = vbNullString)
14241426
If Not evalWithOutVar Then
@@ -1442,7 +1444,7 @@ Public Function InsertField(aIndex As Long, _
14421444
End If
14431445
End If
14441446
End If
1445-
For fCounter = 0 To fldCount
1447+
For fCounter = 0 To FldCount
14461448
If fCounter < aIndex Then
14471449
cpRecord(fCounter) = curRecord(fCounter)
14481450
Else
@@ -1831,7 +1833,7 @@ Private Function SerializeRow(ByRef rArray As Variant) As String
18311833

18321834
LB = LBound(rArray)
18331835
UB = UBound(rArray)
1834-
Jagged = IsJaggedArray(rArray)
1836+
Jagged = isJaggedArray(rArray)
18351837
If Jagged Then 'Recurse
18361838
For i = LB To UB
18371839
If i = LB Then
@@ -2146,9 +2148,9 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
21462148
End If
21472149
On Error Resume Next
21482150
.Eval GetValuesForVariables(rCounter, FilterFields, False, evalRecord)
2149-
If .errorType = ExpressionErrors.errNone Then
2151+
If .ErrorType = ExpressionErrors.errNone Then
21502152
If err.Number = 0 Then
2151-
If CBool(.Result) Then
2153+
If CBool(.result) Then
21522154
'Fill in the data in the table on the right only if the join and predicate are satisfied.
21532155
If lJoinIndex > -1 Then
21542156
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
@@ -2332,9 +2334,9 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
23322334
End If
23332335
On Error Resume Next
23342336
.Eval GetValuesForVariables(rCounter, FilterFields, False, evalRecord)
2335-
If .errorType = ExpressionErrors.errNone Then
2337+
If .ErrorType = ExpressionErrors.errNone Then
23362338
If err.Number = 0 Then
2337-
If CBool(.Result) Then
2339+
If CBool(.result) Then
23382340
'Fill in the data in the table on the left only if the join and predicate are satisfied.
23392341
If lJoinIndex > -1 Then
23402342
For sCounter = 0 To LftTblENDidx
@@ -2513,9 +2515,9 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
25132515
End If
25142516
On Error Resume Next
25152517
.Eval GetValuesForVariables(rCounter, FilterFields, False, evalRecord)
2516-
If .errorType = ExpressionErrors.errNone Then
2518+
If .ErrorType = ExpressionErrors.errNone Then
25172519
If err.Number = 0 Then
2518-
If CBool(.Result) Then
2520+
If CBool(.result) Then
25192521
'Fill in the data in the table.
25202522
If lJoinIndex > -1 Then
25212523
For sCounter = 0 To LftTblENDidx
@@ -2570,19 +2572,19 @@ Private Sub max_heapify(i As Long, _
25702572
HeapSize As Long)
25712573
Dim largest As Long
25722574
Dim l As Long
2573-
Dim r As Long
2575+
Dim R As Long
25742576

25752577
l = 2 * i 'LEFT
2576-
r = 2 * i + 1 'RIGHT
2578+
R = 2 * i + 1 'RIGHT
25772579
largest = i
25782580
If l <= HeapSize Then
25792581
If Buffer(leftt + l - 1)(SortingKey) > Buffer(leftt + i - 1)(SortingKey) Then
25802582
largest = l
25812583
End If
25822584
End If
2583-
If r <= HeapSize Then
2584-
If Buffer(leftt + r - 1)(SortingKey) > Buffer(leftt + largest - 1)(SortingKey) Then
2585-
largest = r
2585+
If R <= HeapSize Then
2586+
If Buffer(leftt + R - 1)(SortingKey) > Buffer(leftt + largest - 1)(SortingKey) Then
2587+
largest = R
25862588
End If
25872589
End If
25882590
If largest <> i Then
@@ -2599,7 +2601,7 @@ End Sub
25992601
''' <param name="R">The index of the last item to be merged.</param>
26002602
''' <param name="SortingKey">The column/key for the logical comparisons.</param>
26012603
''' <param name="Descending">Sort order.</param>
2602-
Private Sub merge(l As Long, m As Long, r As Long, SortingKey As Long, Descending As Boolean)
2604+
Private Sub merge(l As Long, m As Long, R As Long, SortingKey As Long, Descending As Boolean)
26032605

26042606
If Descending Then
26052607
If Buffer(m)(SortingKey) >= Buffer(m + 1)(SortingKey) Then
@@ -2619,7 +2621,7 @@ Private Sub merge(l As Long, m As Long, r As Long, SortingKey As Long, Descendin
26192621
Dim k As Long
26202622

26212623
len1 = m - l + 1
2622-
len2 = r - m
2624+
len2 = R - m
26232625
ReDim leftt(len1 - 1)
26242626
ReDim rightt(len2 - 1)
26252627
For i = 0 To len1 - 1
@@ -2784,7 +2786,7 @@ Private Sub MergeSort_Asc(leftt As Long, _
27842786
pvarMirror As Variant)
27852787
Dim Ulen As Long
27862788
Dim l As Long
2787-
Dim r As Long
2789+
Dim R As Long
27882790
Dim O As Long
27892791
Dim BoolSwitch As Boolean
27902792

@@ -2799,14 +2801,14 @@ Private Sub MergeSort_Asc(leftt As Long, _
27992801
MergeSort_Asc Ulen + 1, rightt, SortingKey, pvarMirror
28002802
' Merge the resulting halves
28012803
l = leftt ' start of first (left) half
2802-
r = Ulen + 1 ' start of second (right) half
2804+
R = Ulen + 1 ' start of second (right) half
28032805
O = leftt ' start of output (mirror array)
28042806
Do
2805-
BoolSwitch = Buffer(r)(SortingKey) < Buffer(l)(SortingKey)
2807+
BoolSwitch = Buffer(R)(SortingKey) < Buffer(l)(SortingKey)
28062808
If BoolSwitch Then
2807-
pvarMirror(O) = Buffer(r)
2808-
r = r + 1
2809-
If r > rightt Then
2809+
pvarMirror(O) = Buffer(R)
2810+
R = R + 1
2811+
If R > rightt Then
28102812
For l = l To Ulen
28112813
O = O + 1
28122814
pvarMirror(O) = Buffer(l)
@@ -2817,9 +2819,9 @@ Private Sub MergeSort_Asc(leftt As Long, _
28172819
pvarMirror(O) = Buffer(l)
28182820
l = l + 1
28192821
If l > Ulen Then
2820-
For r = r To rightt
2822+
For R = R To rightt
28212823
O = O + 1
2822-
pvarMirror(O) = Buffer(r)
2824+
pvarMirror(O) = Buffer(R)
28232825
Next
28242826
Exit Do
28252827
End If
@@ -2841,7 +2843,7 @@ Private Sub MergeSort_Desc(leftt As Long, _
28412843
pvarMirror As Variant)
28422844
Dim Ulen As Long
28432845
Dim l As Long
2844-
Dim r As Long
2846+
Dim R As Long
28452847
Dim O As Long
28462848
Dim BoolSwitch As Boolean
28472849

@@ -2856,14 +2858,14 @@ Private Sub MergeSort_Desc(leftt As Long, _
28562858
MergeSort_Desc Ulen + 1, rightt, SortingKey, pvarMirror
28572859
' Merge the resulting halves
28582860
l = leftt ' start of first (left) half
2859-
r = Ulen + 1 ' start of second (right) half
2861+
R = Ulen + 1 ' start of second (right) half
28602862
O = leftt ' start of output (mirror array)
28612863
Do
2862-
BoolSwitch = Buffer(r)(SortingKey) > Buffer(l)(SortingKey)
2864+
BoolSwitch = Buffer(R)(SortingKey) > Buffer(l)(SortingKey)
28632865
If BoolSwitch Then
2864-
pvarMirror(O) = Buffer(r)
2865-
r = r + 1
2866-
If r > rightt Then
2866+
pvarMirror(O) = Buffer(R)
2867+
R = R + 1
2868+
If R > rightt Then
28672869
For l = l To Ulen
28682870
O = O + 1
28692871
pvarMirror(O) = Buffer(l)
@@ -2874,9 +2876,9 @@ Private Sub MergeSort_Desc(leftt As Long, _
28742876
pvarMirror(O) = Buffer(l)
28752877
l = l + 1
28762878
If l > Ulen Then
2877-
For r = r To rightt
2879+
For R = R To rightt
28782880
O = O + 1
2879-
pvarMirror(O) = Buffer(r)
2881+
pvarMirror(O) = Buffer(R)
28802882
Next
28812883
Exit Do
28822884
End If
@@ -2894,11 +2896,11 @@ End Sub
28942896
''' </summary>
28952897
''' <param name="a">First value.</param>
28962898
''' <param name="b">Second value.</param>
2897-
Private Function Min(a As Long, b As Long) As Long
2898-
If b < a Then
2899+
Private Function Min(A As Long, b As Long) As Long
2900+
If b < A Then
28992901
Min = b
29002902
Else
2901-
Min = a
2903+
Min = A
29022904
End If
29032905
End Function
29042906

@@ -2914,19 +2916,19 @@ Private Sub min_heapify(i As Long, _
29142916
HeapSize As Long)
29152917
Dim smallest As Long
29162918
Dim l As Long
2917-
Dim r As Long
2919+
Dim R As Long
29182920

29192921
l = 2 * i 'LEFT
2920-
r = 2 * i + 1 'RIGHT
2922+
R = 2 * i + 1 'RIGHT
29212923
smallest = i
29222924
If l <= HeapSize Then
29232925
If Buffer(leftt + l - 1)(SortingKey) < Buffer(leftt + i - 1)(SortingKey) Then
29242926
smallest = l
29252927
End If
29262928
End If
2927-
If r <= HeapSize Then
2928-
If Buffer(leftt + r - 1)(SortingKey) < Buffer(leftt + smallest - 1)(SortingKey) Then
2929-
smallest = r
2929+
If R <= HeapSize Then
2930+
If Buffer(leftt + R - 1)(SortingKey) < Buffer(leftt + smallest - 1)(SortingKey) Then
2931+
smallest = R
29302932
End If
29312933
End If
29322934
If smallest <> i Then
@@ -3334,7 +3336,7 @@ Public Function Reduce(ReductionExpression As String, startIndex As Long, _
33343336
On Error Resume Next
33353337
.Eval
33363338
End If
3337-
tmpElement(0) = FormatEvalOutput(.Result)
3339+
tmpElement(0) = FormatEvalOutput(.result)
33383340
tmpResult(0 + rCounter - startIndex + 1) = tmpElement 'reduce
33393341
Next rCounter
33403342
End With
@@ -4133,7 +4135,7 @@ Private Sub TimSort(leftt As Long, rightt As Long, SortingKey As Long, Descendin
41334135
Dim Size As Long
41344136
Dim l As Long
41354137
Dim midd As Long
4136-
Dim r As Long
4138+
Dim R As Long
41374139
Dim i As Long
41384140

41394141
For i = leftt To rightt Step RUN
@@ -4146,11 +4148,11 @@ Private Sub TimSort(leftt As Long, rightt As Long, SortingKey As Long, Descendin
41464148
Do While Size - 1 < rightt
41474149
For l = leftt To rightt Step 2 * Size
41484150
midd = Min(l + Size - 1, rightt)
4149-
r = Min(l + 2 * Size - 1, rightt)
4151+
R = Min(l + 2 * Size - 1, rightt)
41504152
' merge sub array arr[L.....midd] &
41514153
' arr[midd+1....R]
4152-
If midd < r Then
4153-
merge l, midd, r, SortingKey, Descending
4154+
If midd < R Then
4155+
merge l, midd, R, SortingKey, Descending
41544156
End If
41554157
Next l
41564158
Size = 2 * Size

0 commit comments

Comments
 (0)