@@ -509,11 +509,12 @@ Public Sub DumpToJaggedArray(OutPutArray() As Variant, _
509509 OutPutArray() = DataSource.items
510510 End If
511511End Sub
512- Public Sub DumpToSheet (Optional WBookName As String , _
512+ Public Function DumpToSheet (Optional WBookName As String , _
513513 Optional SheetName As String , _
514514 Optional rngName As String = "A1" , _
515515 Optional ByRef DataSource As CSVArrayList = Nothing , _
516- Optional BlockAutoFormat As Boolean = True )
516+ Optional BlockAutoFormat As Boolean = True , _
517+ Optional DrawCellBorders As Boolean = False ) As String
517518 On Error Resume Next
518519 Dim colNumber As Long
519520
@@ -568,13 +569,46 @@ Public Sub DumpToSheet(Optional WBookName As String, _
568569 If BlockAutoFormat Then
569570 .NumberFormat = "@"
570571 End If
571- .Value2 = OutPutArr
572+ .value2 = OutPutArr
573+ If DrawCellBorders Then
574+ 'Left Borders
575+ .Borders(xlEdgeLeft).LineStyle = xlContinuous
576+ .Borders(xlEdgeLeft).ColorIndex = 0
577+ .Borders(xlEdgeLeft).TintAndShade = 0
578+ .Borders(xlEdgeLeft).Weight = xlThin
579+ 'Top Borders
580+ .Borders(xlEdgeTop).LineStyle = xlContinuous
581+ .Borders(xlEdgeTop).ColorIndex = 0
582+ .Borders(xlEdgeTop).TintAndShade = 0
583+ .Borders(xlEdgeTop).Weight = xlThin
584+ 'Bottom Borders
585+ .Borders(xlEdgeBottom).LineStyle = xlContinuous
586+ .Borders(xlEdgeBottom).ColorIndex = 0
587+ .Borders(xlEdgeBottom).TintAndShade = 0
588+ .Borders(xlEdgeBottom).Weight = xlThin
589+ 'Right Borders
590+ .Borders(xlEdgeRight).LineStyle = xlContinuous
591+ .Borders(xlEdgeRight).ColorIndex = 0
592+ .Borders(xlEdgeRight).TintAndShade = 0
593+ .Borders(xlEdgeRight).Weight = xlThin
594+ 'Inside Vertical Borders
595+ .Borders(xlInsideVertical).LineStyle = xlContinuous
596+ .Borders(xlInsideVertical).ColorIndex = 0
597+ .Borders(xlInsideVertical).TintAndShade = 0
598+ .Borders(xlInsideVertical).Weight = xlThin
599+ 'Inside Horizontal Borders
600+ .Borders(xlInsideHorizontal).LineStyle = xlContinuous
601+ .Borders(xlInsideHorizontal).ColorIndex = 0
602+ .Borders(xlInsideHorizontal).TintAndShade = 0
603+ .Borders(xlInsideHorizontal).Weight = xlThin
604+ End If
572605 End With
573606 Erase tmpOutputArray
574607 Erase OutPutArr
575608 EnableOptimization False
609+ DumpToSheet = OutputRange.Address
576610 End If
577- End Sub
611+ End Function
578612Private Sub EnableOptimization (Optional Optimize As Boolean = True )
579613 If Optimize Then
580614 '@------------------------------------------------------
@@ -759,7 +793,7 @@ Public Function GetDataFromCSV(csvPathAndFilename As String) As String
759793 On Error GoTo ErrHandler_GetDataFromCSV
760794 FileHandled = FreeFile
761795 Open csvPathAndFilename For Binary As #FileHandled
762- GetDataFromCSV = Space $(LOF(FileHandled))
796+ GetDataFromCSV = SPACE $(LOF(FileHandled))
763797 Get #FileHandled, , GetDataFromCSV
764798 Close #FileHandled
765799ErrHandler_GetDataFromCSV:
0 commit comments