Skip to content

Commit d8ac926

Browse files
committed
Improvement: fields can now be split into rows
1 parent 1d57e38 commit d8ac926

File tree

5 files changed

+92
-52
lines changed

5 files changed

+92
-52
lines changed

docs/api/methods/splitfield.md

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ Splits the specified field in the imported CSV data.
1515

1616
## Syntax
1717

18-
*expression*.`SplitField`*(aIndex, CharToSplitWith)*
18+
*expression*.`SplitField`*(aIndex, CharToSplitWith, \[RowSplit\])*
1919

2020
### Parameters
2121

@@ -35,6 +35,10 @@ Splits the specified field in the imported CSV data.
3535
<td style="text-align: left;"><em>CharToSplitWith</em></td>
3636
<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>
3737
</tr>
38+
<tr>
39+
<td style="text-align: left;"><em>RowSplit</em></td>
40+
<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>
41+
</tr>
3842
</tbody>
3943
</table>
4044

@@ -64,7 +68,7 @@ Sub SplitField()
6468
With CSVint
6569
.ImportFromCSV .parseConfig
6670
On Error Resume Next
67-
.SplitField 1, "|" 'Split field at index 1 using a pipe character.
71+
.SplitField 1, "|", True 'Split field into new rows at index 1 using a pipe character.
6872
End With
6973
Set CSVint = Nothing
7074
End Sub

src/Access_version.zip

64 Bytes
Binary file not shown.

src/All_Host_version.zip

61 Bytes
Binary file not shown.

src/CSVArrayList.cls

Lines changed: 59 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -155,15 +155,15 @@ End Property
155155
''' <summary>
156156
''' Gets all indexed Items from the current instance.
157157
''' </summary>
158-
Public Property Get Keys() As String()
158+
Public Property Get keys() As String()
159159
Dim tmpResult() As String
160160
Dim iCounter As Long
161161

162162
ReDim tmpResult(0 To IndexedCurrentIndex)
163163
For iCounter = 0 To IndexedCurrentIndex
164164
tmpResult(iCounter) = IndexedBuffer(iCounter).itemKey
165165
Next iCounter
166-
Keys = tmpResult
166+
keys = tmpResult
167167
End Property
168168

169169
''' <summary>
@@ -507,10 +507,10 @@ End Sub
507507
''' </summary>
508508
''' <param name="Keys">Indexes of the fields used for deduplication.</param>
509509
''' <param name="headers">Indicates if the data has a header record.</param>
510-
Public Function Dedupe(Keys As String, Optional Headers As Boolean = True) As CSVArrayList
510+
Public Function Dedupe(keys As String, Optional Headers As Boolean = True) As CSVArrayList
511511
On Error GoTo ErrHandler_Dedupe
512512
Dim aIndexes() As String
513-
aIndexes() = SplitFieldsOrderStr(Keys)
513+
aIndexes() = SplitFieldsOrderStr(keys)
514514
If CheckForDupIndexes(aIndexes) Then
515515
Dim IndexesCollection As Collection
516516
Dim dRecCounter As Long
@@ -532,19 +532,19 @@ Public Function Dedupe(Keys As String, Optional Headers As Boolean = True) As CS
532532
ErrHandler_Dedupe:
533533
Set Dedupe = Nothing
534534
End Function
535-
Private Function DedupeKeysMerge(aIndex As Long, Keys As Variant) As String
535+
Private Function DedupeKeysMerge(aIndex As Long, keys As Variant) As String
536536
Dim tmpResult() As Variant
537537
Dim kLB As Long
538538
Dim kUb As Long
539539
Dim keyCounter As Long
540540
Dim tgRecord() As Variant
541541

542-
kLB = LBound(Keys)
543-
kUb = UBound(Keys)
542+
kLB = LBound(keys)
543+
kUb = UBound(keys)
544544
ReDim tmpResult(kLB To kUb)
545545
tgRecord() = Buffer(aIndex)
546546
For keyCounter = kLB To kUb
547-
tmpResult(keyCounter) = tgRecord(CLng(Keys(keyCounter)))
547+
tmpResult(keyCounter) = tgRecord(CLng(keys(keyCounter)))
548548
Next keyCounter
549549
DedupeKeysMerge = Join$(tmpResult, "|")
550550
End Function
@@ -1582,38 +1582,62 @@ Private Function FormatEvalOutput(ByRef EvalOutput As String) As String
15821582
End If
15831583
End Function
15841584

1585-
Public Function SplitField(aIndex As Long, CharToSplitWith As String) As CSVArrayList
1585+
Public Function SplitField(aIndex As Long, CharToSplitWith As String, _
1586+
Optional RowSplit As Boolean = False) As CSVArrayList
15861587
Dim ColUB As Long
1588+
Dim curRecord() As Variant
1589+
Dim cpRecord() As String
1590+
Dim tmpRecord() As Variant
1591+
Dim rCounter As Long
1592+
Dim rowDiff As Long
1593+
Dim sfldIndex As Long
1594+
Dim lRowIdx As Long
1595+
Dim sfldCPindex As Long
1596+
Dim FldDiff As Long
15871597

15881598
On Error GoTo ErrHandler_SplitField
15891599
ColUB = UBound(Buffer(0))
15901600
Select Case aIndex
15911601
Case 0 To ColUB
1592-
Dim curRecord() As Variant
1593-
Dim cpRecord() As String
1594-
Dim tmpRecord() As Variant
1595-
Dim rCounter As Long
1596-
Dim sfldIndex As Long
1597-
Dim sfldCPindex As Long
1598-
Dim FldDiff As Long
1599-
1600-
For rCounter = 0 To CurrentIndex
1601-
curRecord() = Buffer(rCounter)
1602-
cpRecord() = Split(curRecord(aIndex), CharToSplitWith)
1603-
FldDiff = UBound(cpRecord) - LBound(cpRecord)
1604-
ReDim tmpRecord(0 To ColUB + FldDiff)
1605-
For sfldIndex = 0 To aIndex - 1
1606-
tmpRecord(sfldIndex) = curRecord(sfldIndex)
1607-
Next sfldIndex
1608-
For sfldCPindex = LBound(cpRecord) To UBound(cpRecord)
1609-
tmpRecord(sfldIndex) = cpRecord(sfldCPindex)
1610-
sfldIndex = sfldIndex + 1
1611-
Next sfldCPindex
1612-
For sfldIndex = aIndex + FldDiff + 1 To UBound(curRecord) + FldDiff
1613-
tmpRecord(sfldIndex) = curRecord(sfldIndex - FldDiff)
1614-
Next sfldIndex
1615-
Buffer(rCounter) = tmpRecord
1616-
Next rCounter
1602+
If Not RowSplit Then
1603+
For rCounter = 0 To CurrentIndex
1604+
curRecord() = Buffer(rCounter)
1605+
cpRecord() = Split(curRecord(aIndex), CharToSplitWith)
1606+
FldDiff = UBound(cpRecord) - LBound(cpRecord)
1607+
ReDim tmpRecord(0 To ColUB + FldDiff)
1608+
For sfldIndex = 0 To aIndex - 1
1609+
tmpRecord(sfldIndex) = curRecord(sfldIndex)
1610+
Next sfldIndex
1611+
For sfldCPindex = LBound(cpRecord) To UBound(cpRecord)
1612+
tmpRecord(sfldIndex) = cpRecord(sfldCPindex)
1613+
sfldIndex = sfldIndex + 1
1614+
Next sfldCPindex
1615+
For sfldIndex = aIndex + FldDiff + 1 To UBound(curRecord) + FldDiff
1616+
tmpRecord(sfldIndex) = curRecord(sfldIndex - FldDiff)
1617+
Next sfldIndex
1618+
Buffer(rCounter) = tmpRecord
1619+
Next rCounter
1620+
Else
1621+
rowDiff = 1
1622+
For rCounter = 0 To CurrentIndex
1623+
rowDiff = rowDiff - 1
1624+
curRecord() = Buffer(rCounter + rowDiff)
1625+
cpRecord() = Split(curRecord(aIndex), CharToSplitWith)
1626+
lRowIdx = 0
1627+
For sfldIndex = LBound(cpRecord) To UBound(cpRecord)
1628+
lRowIdx = lRowIdx + 1
1629+
rowDiff = rowDiff + 1
1630+
If lRowIdx = 1 Then
1631+
curRecord(aIndex) = cpRecord(sfldIndex)
1632+
Buffer(rCounter + rowDiff - 1) = curRecord
1633+
Else
1634+
ReDim tmpRecord(0 To ColUB)
1635+
tmpRecord(aIndex) = cpRecord(sfldIndex)
1636+
Me.Insert rCounter + rowDiff - 1, tmpRecord
1637+
End If
1638+
Next sfldIndex
1639+
Next rCounter
1640+
End If
16171641
Case Else
16181642
GoTo OutOfBounds_SplitField
16191643
End Select
@@ -1674,7 +1698,7 @@ Private Function SplitFieldsOrderStr(fieldsString As String) As String()
16741698
End With
16751699
End If
16761700
tmpResult.Sort
1677-
SplitFieldsOrderStr = tmpResult.Keys
1701+
SplitFieldsOrderStr = tmpResult.keys
16781702
Set tmpResult = Nothing
16791703
End Function
16801704
Private Function formatColumnPredicate(predicate As String, _

src/CSVinterface.cls

Lines changed: 27 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -544,7 +544,7 @@ Public Sub DumpToSheet(Optional WBookName As String, _
544544
Set outputSheet = WBook.Sheets(SheetName)
545545
Else
546546
Set outputSheet = WBook.Sheets.Add
547-
outputSheet.Name = SheetName
547+
outputSheet.name = SheetName
548548
End If
549549
'@------------------------------------------------------
550550
'Dump the data
@@ -1643,7 +1643,7 @@ End Function
16431643
Private Function IsSheetInWorkbook(SheetName As String, WBook As Workbook) As Boolean
16441644
With WBook
16451645
On Error Resume Next
1646-
IsSheetInWorkbook = (.Sheets(SheetName).Name = SheetName)
1646+
IsSheetInWorkbook = (.Sheets(SheetName).name = SheetName)
16471647
On Error GoTo 0
16481648
End With
16491649
End Function
@@ -1652,7 +1652,7 @@ Private Function IsWorkbookOpen(WBookName As String) As Boolean
16521652

16531653
On Error Resume Next
16541654
For Each WBook In Workbooks
1655-
BookMatching = (WBook.Name = WBookName)
1655+
BookMatching = (WBook.name = WBookName)
16561656
If BookMatching Then Exit For
16571657
Next
16581658
IsWorkbookOpen = BookMatching
@@ -3303,28 +3303,40 @@ SortByField_Error_Handler:
33033303
P_ERROR_DESC = "[SortByField] " & err.Description
33043304
P_ERROR_SOURCE = err.Source
33053305
End Function
3306-
Public Function SplitField(aIndex As Long, CharToSplitWith As String) As CSVinterface
3306+
Public Function SplitField(aIndex As Long, CharToSplitWith As String, _
3307+
Optional RowSplit As Boolean = False) As CSVinterface
33073308
Dim FldDiff As Long
33083309

33093310
On Error GoTo ErrHandler_SplitField
3310-
If P_SUCCESSFUL_IMPORT And Not P_VARYING_LENGTHS Then
3311-
Select Case aIndex
3312-
Case 0 To P_VECTORS_REGULAR_BOUND
3313-
P_CSV_DATA.SplitField aIndex, CharToSplitWith
3314-
Case Else
3315-
GoTo OutOfBounds_SplitField
3316-
End Select
3311+
If P_SUCCESSFUL_IMPORT Then
3312+
If Not RowSplit Then
3313+
If Not P_VARYING_LENGTHS Then
3314+
Select Case aIndex
3315+
Case 0 To P_VECTORS_REGULAR_BOUND
3316+
P_CSV_DATA.SplitField aIndex, CharToSplitWith
3317+
Case Else
3318+
GoTo OutOfBounds_SplitField
3319+
End Select
3320+
End If
3321+
FldDiff = UBound(P_CSV_DATA(0)) - P_VECTORS_REGULAR_BOUND
3322+
P_VECTORS_REGULAR_BOUND = P_VECTORS_REGULAR_BOUND + FldDiff
3323+
P_VECTORS_MAX_BOUND = P_VECTORS_MAX_BOUND + FldDiff
3324+
Set SplitField = Me
3325+
Else
3326+
Select Case aIndex
3327+
Case 0 To P_VECTORS_REGULAR_BOUND
3328+
P_CSV_DATA.SplitField aIndex, CharToSplitWith, RowSplit
3329+
Case Else
3330+
GoTo OutOfBounds_SplitField
3331+
End Select
3332+
End If
33173333
Else
33183334
P_ERROR_DESC = "[CSV Field Split]: Cannot split the field in the current instance." _
33193335
& " This is because there is no imported data or the records do not " _
33203336
& "have the same number of fields."
33213337
P_ERROR_NUMBER = vbObjectError + 9023
33223338
P_ERROR_SOURCE = "CSVinterface"
33233339
End If
3324-
FldDiff = UBound(P_CSV_DATA(0)) - P_VECTORS_REGULAR_BOUND
3325-
P_VECTORS_REGULAR_BOUND = P_VECTORS_REGULAR_BOUND + FldDiff
3326-
P_VECTORS_MAX_BOUND = P_VECTORS_MAX_BOUND + FldDiff
3327-
Set SplitField = Me
33283340
Exit Function
33293341
ErrHandler_SplitField:
33303342
P_ERROR_DESC = "[CSV Field Split]: " & err.Description

0 commit comments

Comments
 (0)