Skip to content

Commit

Permalink
For release 0.1
Browse files Browse the repository at this point in the history
  • Loading branch information
PGS62 committed Aug 30, 2021
1 parent f27fa78 commit 6f77533
Show file tree
Hide file tree
Showing 20 changed files with 2,825 additions and 1,570 deletions.
1 change: 1 addition & 0 deletions .vscode/settings.json
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
{}
22 changes: 11 additions & 11 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -24,15 +24,15 @@ The documentation borrows freely from that of Julia's [CSV.jl](https://csv.julia
Returns the contents of a comma-separated file on disk as an array.
```vba
Public Function CSVRead(FileName As String, Optional ConvertTypes As Variant = False, _
Optional ByVal Delimiter As Variant, Optional IgnoreRepeated As Boolean, _
Optional DateFormat As String, Optional Comment As String, _
Optional IgnoreEmptyLines As Boolean = True, Optional ByVal HeaderRowNum As Long, _
Optional ByVal SkipToRow As Long = 1, Optional ByVal SkipToCol As Long = 1, _
Optional ByVal NumRows As Long = 0, Optional ByVal NumCols As Long = 0, _
Optional TrueStrings As Variant, Optional FalseStrings As Variant, _
Optional MissingStrings As Variant, Optional ByVal ShowMissingsAs As Variant, _
Optional ByVal Encoding As Variant, Optional DecimalSeparator As String = vbNullString, _
Optional ByRef HeaderRow)
Optional ByVal Delimiter As Variant, Optional IgnoreRepeated As Boolean, _
Optional DateFormat As String, Optional Comment As String, _
Optional IgnoreEmptyLines As Boolean = True, Optional ByVal HeaderRowNum As Long = 0, _
Optional ByVal SkipToRow As Long = 1, Optional ByVal SkipToCol As Long = 1, _
Optional ByVal NumRows As Long = 0, Optional ByVal NumCols As Long = 0, _
Optional TrueStrings As Variant, Optional FalseStrings As Variant, _
Optional MissingStrings As Variant, Optional ByVal ShowMissingsAs As Variant, _
Optional ByVal Encoding As Variant, Optional DecimalSeparator As String = vbNullString, _
Optional ByRef HeaderRow)
```

|Argument|Description|
Expand All @@ -44,8 +44,8 @@ Public Function CSVRead(FileName As String, Optional ConvertTypes As Variant = F
|`DateFormat`|The format of dates in the file such as "Y-M-D", "M-D-Y" or "Y/M/D". Also supports "ISO" for ISO8601 (e.g. 2021-08-26T09:11:30) or "ISOZ" (time zone given e.g. 2021-08-26T13:11:30+05:00), in which case dates-with-time are returned in UTC time.|
|`Comment`|Rows that start with this string will be skipped while parsing.|
|`IgnoreEmptyLines`|Whether empty rows/lines in the file should be skipped while parsing (if FALSE, each column will be assigned `ShowMissingsAs` for that empty row).|
|`HeaderRowNum`|The row in the file containing headers. This argument is most useful when calling from VBA, with `SkipToRow` set to one more than `HeaderRowNum`. In that case the function returns the "data rows", and the header rows are returned via the by-reference argument `HeaderRow`.|
|`SkipToRow`|The first row in the file that's included in the return. Must be at least `HeaderRowNum`, to which it defaults if omitted, but when calling from VBA (rather than an Excel formula) it's often convenient to pass `SkipToRow` as `HeaderRow`+1, so that the function returns the "data rows" and sets the by-reference argument `HeaderRow` equal to the contents of the header row.|
|`HeaderRowNum`|The row in the file containing headers. This argument is most useful when calling from VBA, with `SkipToRow` set to one more than `HeaderRowNum`. In that case the function returns the "data rows", and the header rows are returned via the by-reference argument `HeaderRow`. Optional and defaults to 0.|
|`SkipToRow`|The first row in the file that's included in the return. Optional and defaults to one more than `HeaderRowNum`.|
|`SkipToCol`|The column in the file at which reading starts. Optional and defaults to 1 to read from the first column.|
|`NumRows`|The number of rows to read from the file. If omitted (or zero), all rows from `SkipToRow` to the end of the file are read.|
|`NumCols`|The number of columns to read from the file. If omitted (or zero), all columns from `SkipToCol` are read.|
Expand Down
188 changes: 94 additions & 94 deletions dev/modCSVDevUtils.bas
Original file line number Diff line number Diff line change
Expand Up @@ -15,99 +15,99 @@ Option Explicit
' -----------------------------------------------------------------------------------------------------------------------
Sub SaveWorkbookAndExportModules()

Const Title = "VBA-CSV"
Dim AuditData
Dim BackUpBookName As String
Dim bExport As Boolean
Dim C As VBIDE.VBComponent
Dim FileName As String
Dim Folder As String
Dim Folder2 As String
Dim i As Long
Dim Prompt As String
Dim wb As Workbook

1 On Error GoTo ErrHandler

2 Set wb = ThisWorkbook
3 Folder = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "src"
4 Folder2 = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "dev"

5 Prompt = "Save the workbook and export modules to '" + Folder + "'?"
6 If MsgBox(Prompt, vbOKCancel + vbQuestion, Title) <> vbOK Then Exit Sub

7 If wb.VBProject.Protection = 1 Then
8 Throw "VBProject is protected"
9 Exit Sub
10 End If

11 If Right$(Folder, 1) <> "\" Then Folder = Folder + "\"
12 If Right$(Folder2, 1) <> "\" Then Folder2 = Folder2 + "\"
13 On Error Resume Next
14 Kill Folder & "*.bas*"
15 Kill Folder & "*.cls*"
16 Kill Folder2 & "*.bas*"
17 Kill Folder2 & "*.cls*"
18 On Error GoTo ErrHandler
19 For Each C In wb.VBProject.VBComponents
20 bExport = True
21 FileName = C.Name

22 Select Case C.Type
Case vbext_ct_ClassModule
23 FileName = FileName & ".cls"
24 Case vbext_ct_MSForm
25 FileName = FileName & ".frm"
26 Case vbext_ct_StdModule
27 FileName = FileName & ".bas"
28 Case vbext_ct_Document
29 If C.CodeModule.CountOfLines <= 2 Then 'Only export sheet module if it contains code. Test CountOfLines <= 2 likely to be good enough in practice -
30 bExport = False
31 Else
32 bExport = True
33 FileName = FileName & ".cls"
34 End If
35 Case Else
36 bExport = False
37 End Select

'only export files of the PGS62 project, not those from other _
CSV parsers that I have imported to compare performance.
38 If Left(FileName, 6) <> "modCSV" Then
39 bExport = False
40 End If

41 If bExport Then
42 If FileName = "modCSVReadWrite.bas" Then
43 C.Export Folder & FileName
44 Else
45 C.Export Folder2 & FileName
46 End If
47 End If
48 Next C
49 On Error Resume Next
50 Kill Folder & "*.frx" 'These are binary files that we don't want to check in to Git
51 On Error GoTo ErrHandler
52 AuditData = Range(shAudit.Range("Headers").Cells(1, 1), shAudit.Range("Headers").Cells(1, 1).End(xlToRight).End(xlDown))
53 For i = LBound(AuditData, 1) + 1 To UBound(AuditData, 1)
54 AuditData(i, 3) = CDate(AuditData(i, 3))
55 Next
56 ThrowIfError CSVWrite(AuditData, ThisWorkbook.path & "\AuditSheetComments.csv", True, "dd-mmm-yyyy", "hh:mm:ss")
57 PrepareForRelease
58 ThisWorkbook.Save
59 BackUpBookName = Environ("OneDriveConsumer") + "\Excel Sheets\VBA-CSV_Backups\" + Replace(ThisWorkbook.Name, ".", "_v" & shAudit.Range("B6") & ".")
60 FileCopy ThisWorkbook.FullName, BackUpBookName

61 Exit Sub
Const Title = "VBA-CSV"
Dim AuditData
Dim BackUpBookName As String
Dim bExport As Boolean
Dim c As VBIDE.VBComponent
Dim FileName As String
Dim Folder As String
Dim Folder2 As String
Dim i As Long
Dim Prompt As String
Dim wb As Workbook

On Error GoTo ErrHandler

Set wb = ThisWorkbook
Folder = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "src"
Folder2 = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "dev"

Prompt = "Save the workbook and export modules to '" + Folder + "'?"
If MsgBox(Prompt, vbOKCancel + vbQuestion, Title) <> vbOK Then Exit Sub

If wb.VBProject.Protection = 1 Then
Throw "VBProject is protected"
Exit Sub
End If

If Right$(Folder, 1) <> "\" Then Folder = Folder + "\"
If Right$(Folder2, 1) <> "\" Then Folder2 = Folder2 + "\"
On Error Resume Next
Kill Folder & "*.bas*"
Kill Folder & "*.cls*"
Kill Folder2 & "*.bas*"
Kill Folder2 & "*.cls*"
On Error GoTo ErrHandler

For Each c In wb.VBProject.VBComponents
bExport = True
FileName = c.Name

Select Case c.Type
Case vbext_ct_ClassModule
FileName = FileName & ".cls"
Case vbext_ct_MSForm
FileName = FileName & ".frm"
Case vbext_ct_StdModule
FileName = FileName & ".bas"
Case vbext_ct_Document
If c.CodeModule.CountOfLines <= 2 Then 'Only export sheet module if it contains code. Test CountOfLines <= 2 likely to be good enough in practice -
bExport = False
Else
bExport = True
FileName = FileName & ".cls"
End If
Case Else
bExport = False
End Select

'only export files of the PGS62 project, not those from other _
CSV parsers that I have imported to compare performance.
If Left(FileName, 6) <> "modCSV" Then
bExport = False
End If

If bExport Then
If FileName = "modCSVReadWrite.bas" Then
c.Export Folder & FileName
Else
c.Export Folder2 & FileName
End If
End If
Next c

On Error Resume Next
Kill Folder & "*.frx" 'These are binary files that we don't want to check in to Git
On Error GoTo ErrHandler

AuditData = Range(shAudit.Range("Headers").Cells(1, 1), shAudit.Range("Headers").Cells(1, 1).End(xlToRight).End(xlDown))
For i = LBound(AuditData, 1) + 1 To UBound(AuditData, 1)
AuditData(i, 3) = CDate(AuditData(i, 3))
Next

ThrowIfError CSVWrite(AuditData, ThisWorkbook.path & "\AuditSheetComments.csv", True, "dd-mmm-yyyy", "hh:mm:ss")

PrepareForRelease
ThisWorkbook.Save

BackUpBookName = Environ("OneDriveConsumer") + "\Excel Sheets\VBA-CSV_Backups\" + Replace(ThisWorkbook.Name, ".", "_v" & shAudit.Range("B6") & ".")

FileCopy ThisWorkbook.FullName, BackUpBookName

Exit Sub
ErrHandler:
62 MsgBox "#SaveWorkbookAndExportModules (line " & CStr(Erl) + "): " & Err.Description & "!"
MsgBox "#SaveWorkbookAndExportModules (line " & CStr(Erl) + "): " & Err.Description & "!"
End Sub

' -----------------------------------------------------------------------------------------------------------------------
Expand All @@ -125,15 +125,15 @@ Sub PrepareForRelease()

For Each ws In ThisWorkbook.Worksheets
If ws.Visible = xlSheetVisible Then
Application.GoTo ws.Cells(1, 1)
Application.Goto ws.Cells(1, 1)
ActiveWindow.DisplayGridlines = False
ActiveWindow.DisplayHeadings = False
End If
ws.Protect , True, True
Next
For i = 1 To ThisWorkbook.Worksheets.Count
If ThisWorkbook.Worksheets(i).Visible Then
Application.GoTo ThisWorkbook.Worksheets(i).Cells(1, 1)
Application.Goto ThisWorkbook.Worksheets(i).Cells(1, 1)
Exit For
End If
Next i
Expand Down
Loading

0 comments on commit 6f77533

Please sign in to comment.