Skip to content

Commit

Permalink
mid -> mid$
Browse files Browse the repository at this point in the history
  • Loading branch information
PGS62 committed Sep 9, 2021
1 parent 9f7b62a commit bb740ad
Show file tree
Hide file tree
Showing 11 changed files with 33 additions and 29 deletions.
6 changes: 3 additions & 3 deletions dev/modCSVDevUtils.bas
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,8 @@ Sub SaveWorkbookAndExportModules()
On Error GoTo ErrHandler

Set wb = ThisWorkbook
Folder = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "src"
Folder2 = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "dev"
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
Expand Down Expand Up @@ -74,7 +74,7 @@ Sub SaveWorkbookAndExportModules()

'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
If Left$(FileName, 6) <> "modCSV" Then
bExport = False
End If

Expand Down
6 changes: 3 additions & 3 deletions dev/modCSVPerformance.bas
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ Private Sub RunSpeedTests()

'Julia results file created by function benchmark. See julia/benchmarkCSV.jl, function benchmark

JuliaResultsFile = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "\julia\juliaparsetimes.csv"
JuliaResultsFile = Left$(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "\julia\juliaparsetimes.csv"
If Not FileExists(JuliaResultsFile) Then
Throw "Cannot find file '" + JuliaResultsFile + "'"
End If
Expand Down Expand Up @@ -177,7 +177,7 @@ Function TimeFourParsers(WriteFiles As Boolean, ReadFiles As Boolean, EachFieldC
If VarType(EachFieldContains) = vbDouble Then
ExtraInfo = "Doubles"
ElseIf VarType(EachFieldContains) = vbString Then
If Left(EachFieldContains, 1) = """" And Right(EachFieldContains, 1) = """" Then
If Left$(EachFieldContains, 1) = """" And Right$(EachFieldContains, 1) = """" Then
If InStr(EachFieldContains, vbLf) > 0 Then
ExtraInfo = "Quoted_Strings_with LF_length_" & Len(EachFieldContains)
Else
Expand Down Expand Up @@ -407,7 +407,7 @@ Sub AddChart(Optional xData As Range, Optional yData As Range, Optional Export A
Dim FileName As String
Dim Folder As String
FileName = Replace(TitleCell.Offset(-1).value, " ", "_")
Folder = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "charts\"
Folder = Left$(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "charts\"
ch.Export Folder + FileName
End If

Expand Down
2 changes: 1 addition & 1 deletion dev/modCSVTest.bas
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ Sub RunTests(IncludeLargeFiles As Boolean, ByRef NumPassed As Long, ByRef NumFai

On Error GoTo ErrHandler
Folder = ThisWorkbook.path
Folder = Left(Folder, InStrRev(Folder, "\")) + "testfiles\"
Folder = Left$(Folder, InStrRev(Folder, "\")) + "testfiles\"

If Not FolderExists(Folder) Then Throw "Cannot find folder: '" + Folder + "'"
Test1 Folder, NumPassed, NumFailed, Failures
Expand Down
2 changes: 0 additions & 2 deletions dev/modCSVTestDeps.bas
Original file line number Diff line number Diff line change
Expand Up @@ -915,5 +915,3 @@ Function StringBetweenStrings(TheString, LeftString, RightString, Optional Inclu
ErrHandler:
StringBetweenStrings = "#StringBetweenStrings (line " & CStr(Erl) + "): " & Err.Description & "!"
End Function


2 changes: 1 addition & 1 deletion dev/modCSVTestRDatasets.bas
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ Sub TestAgainstRDatasets()

Dim ResultsFile As String

ResultsFile = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + _
ResultsFile = Left$(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + _
"testresults\SpeedTestRDatasets.csv"

Dim CSVResult
Expand Down
15 changes: 10 additions & 5 deletions dev/modCSVTestRoundTrip.bas
Original file line number Diff line number Diff line change
Expand Up @@ -176,6 +176,11 @@ ErrHandler:
Throw "#RoundTripTestCore: " & Err.Description & "!"
End Sub

Sub sgrsg()
Debug.Print RandomString(False, False, vbLf)
End Sub


Private Function RandomString(AllowLineFeed As Boolean, Unicode As Boolean, EOL As String)

Const maxlen = 20
Expand All @@ -190,22 +195,22 @@ Private Function RandomString(AllowLineFeed As Boolean, Unicode As Boolean, EOL

For i = 1 To length
If Unicode Then
Mid(Res, i, 1) = ChrW(33 + Rnd() * 370)
Mid$(Res, i, 1) = ChrW(33 + Rnd() * 370)
Else
Mid(Res, i, 1) = Chr(34 + Rnd() * 88)
Mid$(Res, i, 1) = Chr(34 + Rnd() * 88)
End If

If Not AllowLineFeed Then
If Mid(Res, i, 1) = vbLf Or Mid(Res, i, 1) = vbCr Then
Mid(Res, i, 1) = " "
If Mid$(Res, i, 1) = vbLf Or Mid$(Res, i, 1) = vbCr Then
Mid$(Res, i, 1) = " "
End If
End If
Next

If AllowLineFeed Then
If length > 5 Then
If Rnd() < 0.2 Then
Mid(Res, length / 2, Len(EOL)) = EOL
Mid$(Res, length / 2, Len(EOL)) = EOL
End If
End If
End If
Expand Down
14 changes: 6 additions & 8 deletions dev/modCSVTestUtils.bas
Original file line number Diff line number Diff line change
Expand Up @@ -43,15 +43,15 @@ Function GenerateTestCode(TestNo As Long, FileName, ExpectedReturn As Variant, C
LitteralExpected = ElementToVBALitteral(ExpectedReturn)
Else
LitteralExpected = ArrayToVBALitteral(ExpectedReturn, , 10000)
If Left(LitteralExpected, 1) = "#" Then
If Left$(LitteralExpected, 1) = "#" Then
End If
End If

Res = Res + vbLf + Indent + "Expected = " & LitteralExpected

Res = Res + vbLf + Indent + "FileName = """ & FileName & """"

If Left(FileName, 4) = "http" Then
If Left$(FileName, 4) = "http" Then
Res = Res + vbLf + Indent + "TestRes = TestCSVRead(" & TestNo & ", TestDescription, Expected, FileName, Observed, WhatDiffers"
Else
Res = Res + vbLf + Indent + "TestRes = TestCSVRead(" & TestNo & ", TestDescription, Expected, Folder + FileName, Observed, WhatDiffers"
Expand Down Expand Up @@ -182,7 +182,7 @@ Function ElementToVBALitteral(x)
ElseIf IsEmpty(x) Then
ElementToVBALitteral = "Empty"
ElseIf IsError(x) Then
ElementToVBALitteral = "CVErr(" & Mid(CStr(x), 7) & ")"
ElementToVBALitteral = "CVErr(" & Mid$(CStr(x), 7) & ")"
End If

Exit Function
Expand Down Expand Up @@ -253,9 +253,9 @@ Function HandleWideString(TheStr As String)
Dim i As Long
Dim Res As String

Res = "ChrW(" + CStr(AscW(Left(TheStr, 1))) + ")"
Res = "ChrW(" + CStr(AscW(Left$(TheStr, 1))) + ")"
For i = 2 To Len(TheStr)
Res = Res + " + ChrW(" + CStr(AscW(Mid(TheStr, i, 1))) + ")"
Res = Res + " + ChrW(" + CStr(AscW(Mid$(TheStr, i, 1))) + ")"
If i Mod 10 = 1 Then
Res = Res + " _" & vbLf
End If
Expand All @@ -272,7 +272,7 @@ Function IsWideString(TheStr As String) As Boolean

On Error GoTo ErrHandler
For i = 1 To Len(TheStr)
If AscW(Mid(TheStr, i, 1)) > 255 Then
If AscW(Mid$(TheStr, i, 1)) > 255 Then
IsWideString = True
End If
Exit For
Expand All @@ -295,5 +295,3 @@ Function UnPack(Str As Variant)
End If
End If
End Function


4 changes: 2 additions & 2 deletions dev/modCSVXLUtils.bas
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ Function TempFolder()
End Function

Function TestFolder()
TestFolder = Left(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "testfiles\"
TestFolder = Left$(ThisWorkbook.path, InStrRev(ThisWorkbook.path, "\")) + "testfiles\"
End Function

'---------------------------------------------------------------------------------------------------------
Expand Down Expand Up @@ -400,7 +400,7 @@ Private Function InsertInString(InsertThis As String, ByVal InToThis As String,
AtPoint = 1
End If

Mid(InToThis, AtPoint, Len(InsertThis)) = InsertThis
Mid$(InToThis, AtPoint, Len(InsertThis)) = InsertThis
InsertInString = InToThis
Exit Function
ErrHandler:
Expand Down
10 changes: 6 additions & 4 deletions src/modCSVReadWrite.bas
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,8 @@ Public Function CSVRead(FileName As String, Optional ConvertTypes As Variant = F
Optional MissingStrings As Variant, Optional ByVal ShowMissingsAs As Variant, _
Optional ByVal Encoding As Variant, Optional DecimalSeparator As String = vbNullString, _
Optional ByRef HeaderRow)
Attribute CSVRead.VB_Description = "Returns the contents of a comma-separated file on disk as an array."
Attribute CSVRead.VB_ProcData.VB_Invoke_Func = " \n14"

Const DQ = """"
Const Err_Delimiter = "Delimiter character must be passed as a string, FALSE for no delimiter. Omit to guess from file contents"
Expand Down Expand Up @@ -2836,6 +2838,8 @@ Public Function CSVWrite(ByVal Data As Variant, Optional FileName As String, _
Optional ByVal DateTimeFormat As String = "ISO", _
Optional Delimiter As String = ",", Optional Unicode As Boolean, _
Optional ByVal EOL As String = "")
Attribute CSVWrite.VB_Description = "Creates a comma-separated file on disk containing Data. Any existing file of the same name is overwritten. If successful, the function returns FileName, otherwise an ""error string"" (starts with `#`, ends with `!`) describing what went wrong."
Attribute CSVWrite.VB_ProcData.VB_Invoke_Func = " \n14"

Const DQ = """"
Const Err_Delimiter = "Delimiter must have at least one character and cannot start with a " & _
Expand Down Expand Up @@ -3461,7 +3465,7 @@ Private Sub CastToTimeB(strIn As String, ByRef dtOut As Date, ByRef Converted As
If SpaceAt = 0 Then SpaceAt = Len(strIn) + 1
FractionalSecond = CDbl(Mid$(strIn, DecPointAt, SpaceAt - DecPointAt)) / 86400

dtOut = CDate(Left$(strIn, DecPointAt - 1) + Mid(strIn, SpaceAt)) + FractionalSecond
dtOut = CDate(Left$(strIn, DecPointAt - 1) + Mid$(strIn, SpaceAt)) + FractionalSecond
Converted = True
Exit Sub
ErrHandler:
Expand Down Expand Up @@ -3729,7 +3733,7 @@ Private Sub SpeedTest_CastISO8601()
PrintThis = "Calls per second = " & Format(N / (t2 - t1), "###,###")
If Len(PrintThis) < 30 Then PrintThis = PrintThis & String(30 - Len(PrintThis), " ")
If Len(strIn) > 30 Then
PrintThis = PrintThis & "strIn = """ & Left(strIn, 27) & "..."""
PrintThis = PrintThis & "strIn = """ & Left$(strIn, 27) & "..."""
Else
PrintThis = PrintThis & "strIn = """ & strIn & """"
End If
Expand Down Expand Up @@ -3791,5 +3795,3 @@ Private Function ISOZFormatString()
ErrHandler:
Throw "#ISOZFormatString: " & Err.Description & "!"
End Function


1 change: 1 addition & 0 deletions workbooks/AuditSheetComments.csv
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
"Version","Date","Time","Author","Comment"
77,09-Sep-2021,10:28:41,"Philip Swannell","mid -> mid$"
76,09-Sep-2021,09:04:37,"Philip Swannell","Ran method AmendVBACode"
75,08-Sep-2021,19:00:28,"Philip Swannell","Docstring changes."
74,08-Sep-2021,09:11:08,"Philip Swannell","Improved ""word-wrapping"" in modCSVReadWrite."
Expand Down
Binary file modified workbooks/VBA-CSV.xlsm
Binary file not shown.

0 comments on commit bb740ad

Please sign in to comment.