@@ -323,7 +323,7 @@ Attribute Add2.VB_Description = "Appends a copy, in jagged array fashion, of the
323
323
Add2 tmpValue
324
324
Next j
325
325
Else
326
- If IsJaggedArray (aValues(i)) Then
326
+ If isJaggedArray (aValues(i)) Then
327
327
For j = LBound(aValues(i)) To UBound(aValues(i))
328
328
Add2 aValues(i)(j)
329
329
Next j
@@ -386,6 +386,8 @@ Public Sub AddIndexedItem(Key As String, iValue As Variant, _
386
386
ReDim Preserve IndexedBuffer(0 To IndexedMaxIndex)
387
387
End If
388
388
If Not P_KEYS_TREE Then
389
+ tmpItem.itemKey = Key
390
+ tmpItem.ItemValue = iValue
389
391
IndexedBuffer(tmpIdx) = tmpItem
390
392
Else
391
393
IndexedBuffer(tmpIdx).itemKey = Key
@@ -726,9 +728,9 @@ Public Function Filter(Pattern As String, startIndex As Long, _
726
728
On Error Resume Next
727
729
.Eval
728
730
End If
729
- If .errorType = ExpressionErrors.errNone Then
731
+ If .ErrorType = ExpressionErrors.errNone Then
730
732
If err.Number = 0 Then
731
- If CBool(.Result ) Then
733
+ If CBool(.result ) Then
732
734
If Not Exclude Then
733
735
Filter.Add Buffer(rCounter) 'Append current record
734
736
End If
@@ -931,7 +933,7 @@ Attribute Concat.VB_Description = "Concatenates the values from the current inst
931
933
Add tmpRow
932
934
Next Dim1Pointer
933
935
Else 'Jagged or 1D array expected
934
- If IsJaggedArray (tmpValues) Then
936
+ If isJaggedArray (tmpValues) Then
935
937
For Dim1Pointer = LBound(tmpValues) To UBound(tmpValues)
936
938
Add tmpValues(Dim1Pointer)
937
939
Next Dim1Pointer
@@ -1356,19 +1358,19 @@ End Sub
1356
1358
''' Returns True if the paseed argument is a jagged array.
1357
1359
''' </summary>
1358
1360
''' <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."
1361
1363
On Error GoTo IsJaggedArray_Err_Handler
1362
1364
If IsArray(arr) Then
1363
1365
If Not MultiDimensional(arr) Then
1364
1366
Dim BoundingTest As Long
1365
1367
BoundingTest = LBound(arr(LBound(arr)))
1366
- IsJaggedArray = True
1368
+ isJaggedArray = True
1367
1369
End If
1368
1370
End If
1369
1371
Exit Function
1370
1372
IsJaggedArray_Err_Handler:
1371
- IsJaggedArray = False
1373
+ isJaggedArray = False
1372
1374
End Function
1373
1375
1374
1376
Private Function Is2Darray (arr As Variant ) As Boolean
@@ -1406,19 +1408,19 @@ Public Function InsertField(aIndex As Long, _
1406
1408
Dim Evaluator As CSVexpressions
1407
1409
Dim evalWithOutVar As Boolean
1408
1410
Dim fCounter As Long
1409
- Dim fldCount As Long
1411
+ Dim FldCount As Long
1410
1412
Dim rCounter As Long
1411
1413
Dim TargetFields() As Long
1412
1414
1413
- fldCount = UBound(Buffer(0 ))
1415
+ FldCount = UBound(Buffer(0 ))
1414
1416
'@--------------------------------------------------------------------------------
1415
1417
'Reserve storage
1416
- ReDim cpRecord(0 To fldCount + 1 )
1418
+ ReDim cpRecord(0 To FldCount + 1 )
1417
1419
cpRecordBK() = cpRecord
1418
1420
Set Evaluator = New CSVexpressions
1419
1421
If Formula <> vbNullString Then
1420
1422
With Evaluator
1421
- .formatResult = True
1423
+ .FormatResult = True
1422
1424
.Create SwitchUnderscoresAndSpaces(Formula, Buffer(0 ))
1423
1425
evalWithOutVar = (.CurrentVariables = vbNullString)
1424
1426
If Not evalWithOutVar Then
@@ -1442,7 +1444,7 @@ Public Function InsertField(aIndex As Long, _
1442
1444
End If
1443
1445
End If
1444
1446
End If
1445
- For fCounter = 0 To fldCount
1447
+ For fCounter = 0 To FldCount
1446
1448
If fCounter < aIndex Then
1447
1449
cpRecord(fCounter) = curRecord(fCounter)
1448
1450
Else
@@ -1831,7 +1833,7 @@ Private Function SerializeRow(ByRef rArray As Variant) As String
1831
1833
1832
1834
LB = LBound(rArray)
1833
1835
UB = UBound(rArray)
1834
- Jagged = IsJaggedArray (rArray)
1836
+ Jagged = isJaggedArray (rArray)
1835
1837
If Jagged Then 'Recurse
1836
1838
For i = LB To UB
1837
1839
If i = LB Then
@@ -2146,9 +2148,9 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
2146
2148
End If
2147
2149
On Error Resume Next
2148
2150
.Eval GetValuesForVariables(rCounter, FilterFields, False , evalRecord)
2149
- If .errorType = ExpressionErrors.errNone Then
2151
+ If .ErrorType = ExpressionErrors.errNone Then
2150
2152
If err.Number = 0 Then
2151
- If CBool(.Result ) Then
2153
+ If CBool(.result ) Then
2152
2154
'Fill in the data in the table on the right only if the join and predicate are satisfied.
2153
2155
If lJoinIndex > -1 Then
2154
2156
For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
@@ -2332,9 +2334,9 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
2332
2334
End If
2333
2335
On Error Resume Next
2334
2336
.Eval GetValuesForVariables(rCounter, FilterFields, False , evalRecord)
2335
- If .errorType = ExpressionErrors.errNone Then
2337
+ If .ErrorType = ExpressionErrors.errNone Then
2336
2338
If err.Number = 0 Then
2337
- If CBool(.Result ) Then
2339
+ If CBool(.result ) Then
2338
2340
'Fill in the data in the table on the left only if the join and predicate are satisfied.
2339
2341
If lJoinIndex > -1 Then
2340
2342
For sCounter = 0 To LftTblENDidx
@@ -2513,9 +2515,9 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
2513
2515
End If
2514
2516
On Error Resume Next
2515
2517
.Eval GetValuesForVariables(rCounter, FilterFields, False , evalRecord)
2516
- If .errorType = ExpressionErrors.errNone Then
2518
+ If .ErrorType = ExpressionErrors.errNone Then
2517
2519
If err.Number = 0 Then
2518
- If CBool(.Result ) Then
2520
+ If CBool(.result ) Then
2519
2521
'Fill in the data in the table.
2520
2522
If lJoinIndex > -1 Then
2521
2523
For sCounter = 0 To LftTblENDidx
@@ -2570,19 +2572,19 @@ Private Sub max_heapify(i As Long, _
2570
2572
HeapSize As Long )
2571
2573
Dim largest As Long
2572
2574
Dim l As Long
2573
- Dim r As Long
2575
+ Dim R As Long
2574
2576
2575
2577
l = 2 * i 'LEFT
2576
- r = 2 * i + 1 'RIGHT
2578
+ R = 2 * i + 1 'RIGHT
2577
2579
largest = i
2578
2580
If l <= HeapSize Then
2579
2581
If Buffer(leftt + l - 1 )(SortingKey) > Buffer(leftt + i - 1 )(SortingKey) Then
2580
2582
largest = l
2581
2583
End If
2582
2584
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
2586
2588
End If
2587
2589
End If
2588
2590
If largest <> i Then
@@ -2599,7 +2601,7 @@ End Sub
2599
2601
''' <param name="R">The index of the last item to be merged.</param>
2600
2602
''' <param name="SortingKey">The column/key for the logical comparisons.</param>
2601
2603
''' <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 )
2603
2605
2604
2606
If Descending Then
2605
2607
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
2619
2621
Dim k As Long
2620
2622
2621
2623
len1 = m - l + 1
2622
- len2 = r - m
2624
+ len2 = R - m
2623
2625
ReDim leftt(len1 - 1 )
2624
2626
ReDim rightt(len2 - 1 )
2625
2627
For i = 0 To len1 - 1
@@ -2784,7 +2786,7 @@ Private Sub MergeSort_Asc(leftt As Long, _
2784
2786
pvarMirror As Variant )
2785
2787
Dim Ulen As Long
2786
2788
Dim l As Long
2787
- Dim r As Long
2789
+ Dim R As Long
2788
2790
Dim O As Long
2789
2791
Dim BoolSwitch As Boolean
2790
2792
@@ -2799,14 +2801,14 @@ Private Sub MergeSort_Asc(leftt As Long, _
2799
2801
MergeSort_Asc Ulen + 1 , rightt, SortingKey, pvarMirror
2800
2802
' Merge the resulting halves
2801
2803
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
2803
2805
O = leftt ' start of output (mirror array)
2804
2806
Do
2805
- BoolSwitch = Buffer(r )(SortingKey) < Buffer(l)(SortingKey)
2807
+ BoolSwitch = Buffer(R )(SortingKey) < Buffer(l)(SortingKey)
2806
2808
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
2810
2812
For l = l To Ulen
2811
2813
O = O + 1
2812
2814
pvarMirror(O) = Buffer(l)
@@ -2817,9 +2819,9 @@ Private Sub MergeSort_Asc(leftt As Long, _
2817
2819
pvarMirror(O) = Buffer(l)
2818
2820
l = l + 1
2819
2821
If l > Ulen Then
2820
- For r = r To rightt
2822
+ For R = R To rightt
2821
2823
O = O + 1
2822
- pvarMirror(O) = Buffer(r )
2824
+ pvarMirror(O) = Buffer(R )
2823
2825
Next
2824
2826
Exit Do
2825
2827
End If
@@ -2841,7 +2843,7 @@ Private Sub MergeSort_Desc(leftt As Long, _
2841
2843
pvarMirror As Variant )
2842
2844
Dim Ulen As Long
2843
2845
Dim l As Long
2844
- Dim r As Long
2846
+ Dim R As Long
2845
2847
Dim O As Long
2846
2848
Dim BoolSwitch As Boolean
2847
2849
@@ -2856,14 +2858,14 @@ Private Sub MergeSort_Desc(leftt As Long, _
2856
2858
MergeSort_Desc Ulen + 1 , rightt, SortingKey, pvarMirror
2857
2859
' Merge the resulting halves
2858
2860
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
2860
2862
O = leftt ' start of output (mirror array)
2861
2863
Do
2862
- BoolSwitch = Buffer(r )(SortingKey) > Buffer(l)(SortingKey)
2864
+ BoolSwitch = Buffer(R )(SortingKey) > Buffer(l)(SortingKey)
2863
2865
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
2867
2869
For l = l To Ulen
2868
2870
O = O + 1
2869
2871
pvarMirror(O) = Buffer(l)
@@ -2874,9 +2876,9 @@ Private Sub MergeSort_Desc(leftt As Long, _
2874
2876
pvarMirror(O) = Buffer(l)
2875
2877
l = l + 1
2876
2878
If l > Ulen Then
2877
- For r = r To rightt
2879
+ For R = R To rightt
2878
2880
O = O + 1
2879
- pvarMirror(O) = Buffer(r )
2881
+ pvarMirror(O) = Buffer(R )
2880
2882
Next
2881
2883
Exit Do
2882
2884
End If
@@ -2894,11 +2896,11 @@ End Sub
2894
2896
''' </summary>
2895
2897
''' <param name="a">First value.</param>
2896
2898
''' <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
2899
2901
Min = b
2900
2902
Else
2901
- Min = a
2903
+ Min = A
2902
2904
End If
2903
2905
End Function
2904
2906
@@ -2914,19 +2916,19 @@ Private Sub min_heapify(i As Long, _
2914
2916
HeapSize As Long )
2915
2917
Dim smallest As Long
2916
2918
Dim l As Long
2917
- Dim r As Long
2919
+ Dim R As Long
2918
2920
2919
2921
l = 2 * i 'LEFT
2920
- r = 2 * i + 1 'RIGHT
2922
+ R = 2 * i + 1 'RIGHT
2921
2923
smallest = i
2922
2924
If l <= HeapSize Then
2923
2925
If Buffer(leftt + l - 1 )(SortingKey) < Buffer(leftt + i - 1 )(SortingKey) Then
2924
2926
smallest = l
2925
2927
End If
2926
2928
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
2930
2932
End If
2931
2933
End If
2932
2934
If smallest <> i Then
@@ -3334,7 +3336,7 @@ Public Function Reduce(ReductionExpression As String, startIndex As Long, _
3334
3336
On Error Resume Next
3335
3337
.Eval
3336
3338
End If
3337
- tmpElement(0 ) = FormatEvalOutput(.Result )
3339
+ tmpElement(0 ) = FormatEvalOutput(.result )
3338
3340
tmpResult(0 + rCounter - startIndex + 1 ) = tmpElement 'reduce
3339
3341
Next rCounter
3340
3342
End With
@@ -4133,7 +4135,7 @@ Private Sub TimSort(leftt As Long, rightt As Long, SortingKey As Long, Descendin
4133
4135
Dim Size As Long
4134
4136
Dim l As Long
4135
4137
Dim midd As Long
4136
- Dim r As Long
4138
+ Dim R As Long
4137
4139
Dim i As Long
4138
4140
4139
4141
For i = leftt To rightt Step RUN
@@ -4146,11 +4148,11 @@ Private Sub TimSort(leftt As Long, rightt As Long, SortingKey As Long, Descendin
4146
4148
Do While Size - 1 < rightt
4147
4149
For l = leftt To rightt Step 2 * Size
4148
4150
midd = Min(l + Size - 1 , rightt)
4149
- r = Min(l + 2 * Size - 1 , rightt)
4151
+ R = Min(l + 2 * Size - 1 , rightt)
4150
4152
' merge sub array arr[L.....midd] &
4151
4153
' 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
4154
4156
End If
4155
4157
Next l
4156
4158
Size = 2 * Size
0 commit comments