Skip to content

Commit

Permalink
Improvement: fields can now be split into rows
Browse files Browse the repository at this point in the history
  • Loading branch information
ws-garcia committed Jul 18, 2023
1 parent 1d57e38 commit d8ac926
Show file tree
Hide file tree
Showing 5 changed files with 92 additions and 52 deletions.
8 changes: 6 additions & 2 deletions docs/api/methods/splitfield.md
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ Splits the specified field in the imported CSV data.

## Syntax

*expression*.`SplitField`*(aIndex, CharToSplitWith)*
*expression*.`SplitField`*(aIndex, CharToSplitWith, \[RowSplit\])*

### Parameters

Expand All @@ -35,6 +35,10 @@ Splits the specified field in the imported CSV data.
<td style="text-align: left;"><em>CharToSplitWith</em></td>
<td style="text-align: left;">Required. Identifier specifying a <code>String</code> Type variable. Represents the character to be used in the split operation.</td>
</tr>
<tr>
<td style="text-align: left;"><em>RowSplit</em></td>
<td style="text-align: left;">Optional. Identifier specifying a <code>Boolean</code> Type variable. Determines when the field is split into new columns or rows.</td>
</tr>
</tbody>
</table>

Expand Down Expand Up @@ -64,7 +68,7 @@ Sub SplitField()
With CSVint
.ImportFromCSV .parseConfig
On Error Resume Next
.SplitField 1, "|" 'Split field at index 1 using a pipe character.
.SplitField 1, "|", True 'Split field into new rows at index 1 using a pipe character.
End With
Set CSVint = Nothing
End Sub
Expand Down
Binary file modified src/Access_version.zip
Binary file not shown.
Binary file modified src/All_Host_version.zip
Binary file not shown.
94 changes: 59 additions & 35 deletions src/CSVArrayList.cls
Original file line number Diff line number Diff line change
Expand Up @@ -155,15 +155,15 @@ End Property
''' <summary>
''' Gets all indexed Items from the current instance.
''' </summary>
Public Property Get Keys() As String()
Public Property Get keys() As String()
Dim tmpResult() As String
Dim iCounter As Long

ReDim tmpResult(0 To IndexedCurrentIndex)
For iCounter = 0 To IndexedCurrentIndex
tmpResult(iCounter) = IndexedBuffer(iCounter).itemKey
Next iCounter
Keys = tmpResult
keys = tmpResult
End Property

''' <summary>
Expand Down Expand Up @@ -507,10 +507,10 @@ End Sub
''' </summary>
''' <param name="Keys">Indexes of the fields used for deduplication.</param>
''' <param name="headers">Indicates if the data has a header record.</param>
Public Function Dedupe(Keys As String, Optional Headers As Boolean = True) As CSVArrayList
Public Function Dedupe(keys As String, Optional Headers As Boolean = True) As CSVArrayList
On Error GoTo ErrHandler_Dedupe
Dim aIndexes() As String
aIndexes() = SplitFieldsOrderStr(Keys)
aIndexes() = SplitFieldsOrderStr(keys)
If CheckForDupIndexes(aIndexes) Then
Dim IndexesCollection As Collection
Dim dRecCounter As Long
Expand All @@ -532,19 +532,19 @@ Public Function Dedupe(Keys As String, Optional Headers As Boolean = True) As CS
ErrHandler_Dedupe:
Set Dedupe = Nothing
End Function
Private Function DedupeKeysMerge(aIndex As Long, Keys As Variant) As String
Private Function DedupeKeysMerge(aIndex As Long, keys As Variant) As String
Dim tmpResult() As Variant
Dim kLB As Long
Dim kUb As Long
Dim keyCounter As Long
Dim tgRecord() As Variant

kLB = LBound(Keys)
kUb = UBound(Keys)
kLB = LBound(keys)
kUb = UBound(keys)
ReDim tmpResult(kLB To kUb)
tgRecord() = Buffer(aIndex)
For keyCounter = kLB To kUb
tmpResult(keyCounter) = tgRecord(CLng(Keys(keyCounter)))
tmpResult(keyCounter) = tgRecord(CLng(keys(keyCounter)))
Next keyCounter
DedupeKeysMerge = Join$(tmpResult, "|")
End Function
Expand Down Expand Up @@ -1582,38 +1582,62 @@ Private Function FormatEvalOutput(ByRef EvalOutput As String) As String
End If
End Function

Public Function SplitField(aIndex As Long, CharToSplitWith As String) As CSVArrayList
Public Function SplitField(aIndex As Long, CharToSplitWith As String, _
Optional RowSplit As Boolean = False) As CSVArrayList
Dim ColUB As Long
Dim curRecord() As Variant
Dim cpRecord() As String
Dim tmpRecord() As Variant
Dim rCounter As Long
Dim rowDiff As Long
Dim sfldIndex As Long
Dim lRowIdx As Long
Dim sfldCPindex As Long
Dim FldDiff As Long

On Error GoTo ErrHandler_SplitField
ColUB = UBound(Buffer(0))
Select Case aIndex
Case 0 To ColUB
Dim curRecord() As Variant
Dim cpRecord() As String
Dim tmpRecord() As Variant
Dim rCounter As Long
Dim sfldIndex As Long
Dim sfldCPindex As Long
Dim FldDiff As Long

For rCounter = 0 To CurrentIndex
curRecord() = Buffer(rCounter)
cpRecord() = Split(curRecord(aIndex), CharToSplitWith)
FldDiff = UBound(cpRecord) - LBound(cpRecord)
ReDim tmpRecord(0 To ColUB + FldDiff)
For sfldIndex = 0 To aIndex - 1
tmpRecord(sfldIndex) = curRecord(sfldIndex)
Next sfldIndex
For sfldCPindex = LBound(cpRecord) To UBound(cpRecord)
tmpRecord(sfldIndex) = cpRecord(sfldCPindex)
sfldIndex = sfldIndex + 1
Next sfldCPindex
For sfldIndex = aIndex + FldDiff + 1 To UBound(curRecord) + FldDiff
tmpRecord(sfldIndex) = curRecord(sfldIndex - FldDiff)
Next sfldIndex
Buffer(rCounter) = tmpRecord
Next rCounter
If Not RowSplit Then
For rCounter = 0 To CurrentIndex
curRecord() = Buffer(rCounter)
cpRecord() = Split(curRecord(aIndex), CharToSplitWith)
FldDiff = UBound(cpRecord) - LBound(cpRecord)
ReDim tmpRecord(0 To ColUB + FldDiff)
For sfldIndex = 0 To aIndex - 1
tmpRecord(sfldIndex) = curRecord(sfldIndex)
Next sfldIndex
For sfldCPindex = LBound(cpRecord) To UBound(cpRecord)
tmpRecord(sfldIndex) = cpRecord(sfldCPindex)
sfldIndex = sfldIndex + 1
Next sfldCPindex
For sfldIndex = aIndex + FldDiff + 1 To UBound(curRecord) + FldDiff
tmpRecord(sfldIndex) = curRecord(sfldIndex - FldDiff)
Next sfldIndex
Buffer(rCounter) = tmpRecord
Next rCounter
Else
rowDiff = 1
For rCounter = 0 To CurrentIndex
rowDiff = rowDiff - 1
curRecord() = Buffer(rCounter + rowDiff)
cpRecord() = Split(curRecord(aIndex), CharToSplitWith)
lRowIdx = 0
For sfldIndex = LBound(cpRecord) To UBound(cpRecord)
lRowIdx = lRowIdx + 1
rowDiff = rowDiff + 1
If lRowIdx = 1 Then
curRecord(aIndex) = cpRecord(sfldIndex)
Buffer(rCounter + rowDiff - 1) = curRecord
Else
ReDim tmpRecord(0 To ColUB)
tmpRecord(aIndex) = cpRecord(sfldIndex)
Me.Insert rCounter + rowDiff - 1, tmpRecord
End If
Next sfldIndex
Next rCounter
End If
Case Else
GoTo OutOfBounds_SplitField
End Select
Expand Down Expand Up @@ -1674,7 +1698,7 @@ Private Function SplitFieldsOrderStr(fieldsString As String) As String()
End With
End If
tmpResult.Sort
SplitFieldsOrderStr = tmpResult.Keys
SplitFieldsOrderStr = tmpResult.keys
Set tmpResult = Nothing
End Function
Private Function formatColumnPredicate(predicate As String, _
Expand Down
42 changes: 27 additions & 15 deletions src/CSVinterface.cls
Original file line number Diff line number Diff line change
Expand Up @@ -544,7 +544,7 @@ Public Sub DumpToSheet(Optional WBookName As String, _
Set outputSheet = WBook.Sheets(SheetName)
Else
Set outputSheet = WBook.Sheets.Add
outputSheet.Name = SheetName
outputSheet.name = SheetName
End If
'@------------------------------------------------------
'Dump the data
Expand Down Expand Up @@ -1643,7 +1643,7 @@ End Function
Private Function IsSheetInWorkbook(SheetName As String, WBook As Workbook) As Boolean
With WBook
On Error Resume Next
IsSheetInWorkbook = (.Sheets(SheetName).Name = SheetName)
IsSheetInWorkbook = (.Sheets(SheetName).name = SheetName)
On Error GoTo 0
End With
End Function
Expand All @@ -1652,7 +1652,7 @@ Private Function IsWorkbookOpen(WBookName As String) As Boolean

On Error Resume Next
For Each WBook In Workbooks
BookMatching = (WBook.Name = WBookName)
BookMatching = (WBook.name = WBookName)
If BookMatching Then Exit For
Next
IsWorkbookOpen = BookMatching
Expand Down Expand Up @@ -3303,28 +3303,40 @@ SortByField_Error_Handler:
P_ERROR_DESC = "[SortByField] " & err.Description
P_ERROR_SOURCE = err.Source
End Function
Public Function SplitField(aIndex As Long, CharToSplitWith As String) As CSVinterface
Public Function SplitField(aIndex As Long, CharToSplitWith As String, _
Optional RowSplit As Boolean = False) As CSVinterface
Dim FldDiff As Long

On Error GoTo ErrHandler_SplitField
If P_SUCCESSFUL_IMPORT And Not P_VARYING_LENGTHS Then
Select Case aIndex
Case 0 To P_VECTORS_REGULAR_BOUND
P_CSV_DATA.SplitField aIndex, CharToSplitWith
Case Else
GoTo OutOfBounds_SplitField
End Select
If P_SUCCESSFUL_IMPORT Then
If Not RowSplit Then
If Not P_VARYING_LENGTHS Then
Select Case aIndex
Case 0 To P_VECTORS_REGULAR_BOUND
P_CSV_DATA.SplitField aIndex, CharToSplitWith
Case Else
GoTo OutOfBounds_SplitField
End Select
End If
FldDiff = UBound(P_CSV_DATA(0)) - P_VECTORS_REGULAR_BOUND
P_VECTORS_REGULAR_BOUND = P_VECTORS_REGULAR_BOUND + FldDiff
P_VECTORS_MAX_BOUND = P_VECTORS_MAX_BOUND + FldDiff
Set SplitField = Me
Else
Select Case aIndex
Case 0 To P_VECTORS_REGULAR_BOUND
P_CSV_DATA.SplitField aIndex, CharToSplitWith, RowSplit
Case Else
GoTo OutOfBounds_SplitField
End Select
End If
Else
P_ERROR_DESC = "[CSV Field Split]: Cannot split the field in the current instance." _
& " This is because there is no imported data or the records do not " _
& "have the same number of fields."
P_ERROR_NUMBER = vbObjectError + 9023
P_ERROR_SOURCE = "CSVinterface"
End If
FldDiff = UBound(P_CSV_DATA(0)) - P_VECTORS_REGULAR_BOUND
P_VECTORS_REGULAR_BOUND = P_VECTORS_REGULAR_BOUND + FldDiff
P_VECTORS_MAX_BOUND = P_VECTORS_MAX_BOUND + FldDiff
Set SplitField = Me
Exit Function
ErrHandler_SplitField:
P_ERROR_DESC = "[CSV Field Split]: " & err.Description
Expand Down

0 comments on commit d8ac926

Please sign in to comment.