@@ -562,7 +562,7 @@ Public Function Filter(Pattern As String, startIndex As Long, _
562562 .Eval GetValuesForVariables(rCounter, TargetFields)
563563 If .ErrorType = ExpressionErrors.errNone Then
564564 If err.Number = 0 Then
565- If CBool(.Result ) Then
565+ If CBool(.result ) Then
566566 If Not Exclude Then
567567 Filter.Add Buffer(rCounter) 'Append current record
568568 End If
@@ -910,7 +910,7 @@ Public Function Group(Table As CSVArrayList, By As Variant, OperateOn As Variant
910910 GroupFIdx = 1 'Base 1 input
911911 End If
912912 Else
913- GroupFIdx = Abs(By) - deltaPos + 1
913+ GroupFIdx = Abs(By)
914914 End If
915915 If Not IsNumeric(OperateOn) Then
916916 If Headers Then
@@ -919,7 +919,7 @@ Public Function Group(Table As CSVArrayList, By As Variant, OperateOn As Variant
919919 OperateFidx = 1 'Base 1 input
920920 End If
921921 Else
922- OperateFidx = Abs(OperateOn) - deltaPos + 1
922+ OperateFidx = Abs(OperateOn)
923923 End If
924924 'Save first row
925925 If Headers Then
@@ -1276,6 +1276,7 @@ Public Function SplitFieldsOrderStr(fieldsString As String) As String()
12761276 Dim tmpResult As CSVArrayList
12771277
12781278 Set tmpResult = New CSVArrayList
1279+ tmpResult.Indexing = True
12791280 tmpPreResult() = Split(Join$(Split(fieldsString, " " ), vbNullString), d_comma)
12801281 If fieldsString Like "*-*" Then
12811282 Dim rfJCounter As Long
@@ -1296,31 +1297,25 @@ Public Function SplitFieldsOrderStr(fieldsString As String) As String()
12961297 End If
12971298 With tmpResult
12981299 For rfJCounter = ROFlb To ROFub Step stepIdx
1299- If .ItemIndex(CStr(rfJCounter), 1 ) = -1 Then
1300- .Add2 CStr(rfJCounter)
1301- End If
1300+ .AddIndexedItem CStr(rfJCounter), CStr(rfJCounter)
13021301 Next rfJCounter
13031302 End With
13041303 Else
13051304 With tmpResult
1306- If Not .ItemExist(tmpPreResult(rfICounter), 1 ) Then
1307- .Add2 tmpPreResult(rfICounter)
1308- End If
1305+ .AddIndexedItem tmpPreResult(rfICounter), tmpPreResult(rfICounter)
13091306 End With
13101307 End If
13111308 Next rfICounter
13121309 Else
13131310 With tmpResult
13141311 For rfICounter = LBound(tmpPreResult) To UBound(tmpPreResult)
1315- If .ItemIndex(CStr(rfJCounter), 1 ) = -1 Then
1316- tmpResult.Add2 tmpPreResult(rfICounter)
1317- End If
1312+ .AddIndexedItem tmpPreResult(rfICounter), tmpPreResult(rfICounter)
13181313 Next rfICounter
13191314 End With
13201315 End If
13211316 ReDim tmpFields(0 To tmpResult.count - 1 )
13221317 For rfICounter = 0 To tmpResult.count - 1
1323- tmpFields(rfICounter) = tmpResult.Item (rfICounter)( 0 )
1318+ tmpFields(rfICounter) = tmpResult(rfICounter)
13241319 Next rfICounter
13251320 SplitFieldsOrderStr = tmpFields
13261321 Set tmpResult = Nothing
@@ -1601,7 +1596,7 @@ Public Function LeftJoin(ByRef leftTable As CSVArrayList, _
16011596 .Eval GetValuesForVariables(rCounter, FilterFields, False , evalRecord)
16021597 If .ErrorType = ExpressionErrors.errNone Then
16031598 If err.Number = 0 Then
1604- If CBool(.Result ) Then
1599+ If CBool(.result ) Then
16051600 'Fill in the data in the table on the left only if the join and predicate are satisfied.
16061601 If lJoinIndex > -1 Then
16071602 For sCounter = LftTblENDidx + 1 To UBound(resultRecord)
@@ -1769,7 +1764,7 @@ Public Function RightJoin(ByRef leftTable As CSVArrayList, _
17691764 .Eval GetValuesForVariables(rCounter, FilterFields, False , evalRecord)
17701765 If .ErrorType = ExpressionErrors.errNone Then
17711766 If err.Number = 0 Then
1772- If CBool(.Result ) Then
1767+ If CBool(.result ) Then
17731768 'Fill in the data in the table on the left only if the join and predicate are satisfied.
17741769 If lJoinIndex > -1 Then
17751770 For sCounter = 0 To LftTblENDidx
@@ -1932,7 +1927,7 @@ Public Function InnerJoin(ByRef leftTable As CSVArrayList, _
19321927 .Eval GetValuesForVariables(rCounter, FilterFields, False , evalRecord)
19331928 If .ErrorType = ExpressionErrors.errNone Then
19341929 If err.Number = 0 Then
1935- If CBool(.Result ) Then
1930+ If CBool(.result ) Then
19361931 'Fill in the data in the table.
19371932 If lJoinIndex > -1 Then
19381933 For sCounter = 0 To LftTblENDidx
@@ -2640,7 +2635,7 @@ Public Function Reduce(ReductionExpression As String, startIndex As Long, endInd
26402635 For rCounter = startIndex - 1 To endIndex - 1
26412636 On Error Resume Next
26422637 .Eval GetValuesForVariables(rCounter, TargetFields)
2643- tmpResult(0 + rCounter - startIndex + 1 ) = .Result 'reduce
2638+ tmpResult(0 + rCounter - startIndex + 1 ) = .result 'reduce
26442639 Next rCounter
26452640 End With
26462641 Reduce = tmpResult
@@ -2817,7 +2812,7 @@ End Function
28172812''' Searches for a key in the internal indexed records
28182813''' </summary>
28192814''' <param name="TargetKey">The key to be searched.</param>
2820- Public Function KeyExist (ByRef TargetKey As String ) As Long
2815+ Public Function KeyExist (ByRef TargetKey As String ) As Boolean
28212816 KeyExist = (KeyIndex(TargetKey) > -1 )
28222817End Function
28232818''' <summary>
@@ -2841,7 +2836,7 @@ Public Function KeyIndex(ByRef TargetKey As String) As Long
28412836 BottomIdx = 0
28422837 TopIdx = IndexedCurrentIndex
28432838 Do
2844- MiddleIdx = BottomIdx + ((TopIdx - BottomIdx) / 2 )
2839+ MiddleIdx = BottomIdx + Ceiling ((TopIdx - BottomIdx) / 2 )
28452840 tmpR = (TargetKey = IndexedBuffer(MiddleIdx).ItemKey)
28462841 If TargetKey > IndexedBuffer(MiddleIdx).ItemKey Then
28472842 BottomIdx = MiddleIdx + 1
0 commit comments