Skip to content

Commit 08ee3ad

Browse files
authored
Merge pull request #6 from ws-garcia/dump-data-to-sheet-method
Add DumpToSheet method, update docs repo
2 parents 38f7f26 + 5df0ea8 commit 08ee3ad

File tree

9 files changed

+164
-12
lines changed

9 files changed

+164
-12
lines changed

docs/api/methods/dumptoarray.md

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -29,19 +29,19 @@ _None_
2929

3030
## Remarks
3131

32-
**Note**: *Before dump data, is recommended to make a `ImportFromCSV` method call.*
32+
**Note**: *Before dump data, is recommended to make a `ImportFromCSV` or `ImportFromCSVstring` method call.*
3333

3434
The *OutPutArray* parameter must be declared as dynamic `String` array. If user forget to do this, an error will occur.
3535

3636
See also
37-
: [ImportFromCSV method](https://ws-garcia.github.io/VBA-CSV-interface/api/methods/importfromcsv.html).
37+
: [ImportFromCSV method](https://ws-garcia.github.io/VBA-CSV-interface/api/methods/importfromcsv.html), [ImportFromCSVstring method](https://ws-garcia.github.io/VBA-CSV-interface/api/methods/importfromcsvstring.html).
3838

3939
---
4040

4141
## Behavior
4242

4343
The `DumpToArray` method make a copy of all the data stored in the current instance. The data is returned in the *OutPutArray* parameter for avoid additional data copies in the internals.
4444

45-
The dumped data will be erased from memory, in other words, the current instance doesn't hold the CSV read data any more. In the same way, the `DumpToArray` method returns an empty `String` array for subsequent calls not preceded by `ImportFromCSV` method call.
45+
The dumped data will be erased from memory, in other words, the current instance doesn't hold the CSV read data any more. In the same way, the `DumpToArray` method returns an empty `String` array for subsequent calls not preceded by `ImportFromCSV` or or `ImportFromCSVstring` method call.
4646

4747
[Back to Methods overview](https://ws-garcia.github.io/VBA-CSV-interface/api/methods/)

docs/api/methods/dumptosheet.md

Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,64 @@
1+
---
2+
title: DumpToSheet
3+
parent: Methods
4+
grand_parent: API
5+
nav_order: 2
6+
---
7+
8+
# DumpToSheet
9+
{: .fs-9 }
10+
11+
Dumps the data from the current instance to an Excel WorkSheet.
12+
{: .fs-6 .fw-300 }
13+
14+
---
15+
16+
## Syntax
17+
18+
*expression*.`DumpToSheet`*({WBookName}, {SheetName}, {RngName})*
19+
20+
### Parameters
21+
22+
<table>
23+
<thead>
24+
<tr>
25+
<th style="text-align: left;">Part</th>
26+
<th style="text-align: left;">Description</th>
27+
</tr>
28+
</thead>
29+
<tbody>
30+
<tr>
31+
<td style="text-align: left;"><em>WBookName</em></td>
32+
<td style="text-align: left;">Optional. Identifier specifying a <code>String</code> variable representing the output Workbook name.</td>
33+
</tr>
34+
<tr>
35+
<td style="text-align: left;"><em>SheetName</em></td>
36+
<td style="text-align: left;">Optional. Identifier specifying a <code>String</code> variable representing the output Worksheet name.</td>
37+
</tr>
38+
<tr>
39+
<td style="text-align: left;"><em>RngName</em></td>
40+
<td style="text-align: left;">Optional. Identifier specifying a <code>String</code> variable representing the name of the output top left-most range.</td>
41+
</tr>
42+
</tbody>
43+
</table>
44+
45+
### Return value
46+
47+
_None_
48+
49+
---
50+
51+
## Remarks
52+
53+
**Note**: *Before dump data, is recommended to make a `ImportFromCSV` or `ImportFromCSVstring` method call.*
54+
55+
See also
56+
: [ImportFromCSV method](https://ws-garcia.github.io/VBA-CSV-interface/api/methods/importfromcsv.html), [ImportFromCSVstring method](https://ws-garcia.github.io/VBA-CSV-interface/api/methods/importfromcsvstring.html).
57+
58+
---
59+
60+
## Behavior
61+
62+
When the *WBookName* parameter is omitted the data is dumped into the Workbook that holds the CSV interface's *VBAProject*. Omitting the *SheetName* parameter adds a new Worksheet to the desired Workbook. Also, if the *RngName* parameter is omitted the data will dumped starting on the "A1" named cell in the desired Worksheet.
63+
64+
[Back to Methods overview](https://ws-garcia.github.io/VBA-CSV-interface/api/methods/)

docs/api/methods/exporttocsv.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
title: ExportToCSV
33
parent: Methods
44
grand_parent: API
5-
nav_order: 2
5+
nav_order: 3
66
---
77

88
# ExportToCSV

docs/api/methods/getdatafromcsv.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
title: GetDataFromCSV
33
parent: Methods
44
grand_parent: API
5-
nav_order: 3
5+
nav_order: 4
66
---
77

88
# GetDataFromCSV

docs/api/methods/importfromcsv.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
title: ImportFromCSV
33
parent: Methods
44
grand_parent: API
5-
nav_order: 4
5+
nav_order: 5
66
---
77

88
# ImportFromCSV

docs/api/methods/importfromcsvstring.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
title: ImportFromCSVstring
33
parent: Methods
44
grand_parent: API
5-
nav_order: 5
5+
nav_order: 6
66
---
77

88
# ImportFromCSVstring

docs/api/methods/openconnection.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
title: OpenConnection
33
parent: Methods
44
grand_parent: API
5-
nav_order: 6
5+
nav_order: 7
66
---
77

88
# OpenConnection

docs/api/methods/resettodefault.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
title: ResetToDefault
33
parent: Methods
44
grand_parent: API
5-
nav_order: 7
5+
nav_order: 8
66
---
77

88
# ResetToDefault

src/CSVinterface.cls

Lines changed: 91 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ Attribute VB_Exposed = False
3333
'#
3434
' Use CSVinterface class to simplify the work with comma separated value (CSV) files.
3535
' It allow you to exchange information betwen an VBA array and an external CSV file without
36-
' using Excel WorkSheets, neigter any external reference such as [MS Scripting Runtime].
36+
' using Excel Worksheets, neigter any external reference such as [MS Scripting Runtime].
3737
' The class develop is focusing in the code execution performance.
3838
'#
3939
' Feel free to visit the cited websites to explore some of the available solutions for
@@ -60,13 +60,14 @@ Attribute VB_Exposed = False
6060
' @1 https://senipah.github.io/VBA-Better-Array
6161
' @2 https://github.com/sdkn104/VBA-CSV
6262
' @3 http://www.vbaexpress.com/forum/showthread.php?25095-Solved-Check-the-file-encode-type
63-
' @4 https://www.codegrepper.com/code-examples/vb/excel+vba+Load+csv+file+into+an+array+rather+than+the+worksheet
63+
' @4 https://www.codegrepper.com/code-examples/vb/excel+vba+Load+csv+file+into+an+array+rather+than+the+Worksheet
6464
' @5 http://excellerando.blogspot.com/2014/12/writing-excel-range-to-csv-file.html
6565
' @6 https://stackoverflow.com/questions/4191560/create-csv-from-array-in-vba
6666
' @7 https://www.freevbcode.com/ShowCode.asp?ID=3110
6767
' @8 https://stackoverflow.com/questions/1376756/what-is-a-superfast-way-to-read-large-files-line-by-line-in-vba
6868
' @9 https://www.freevbcode.com/ShowCode.asp?ID=7655
69-
69+
' @10 http://www.cpearson.com/excel/mainpage.aspx
70+
' @11 https://www.exceltip.com/excel-macros-and-vba
7071
'////////////////////////////////////////////////////////////////////////////////////////////
7172
'#
7273
Option Explicit
@@ -293,6 +294,63 @@ Attribute DumpToArray.VB_UserMemId = 0
293294
OutPutArray() = P_CSV_DATA
294295
Erase P_CSV_DATA
295296
End Sub
297+
Public Sub DumpToSheet(Optional WBookName As String, _
298+
Optional SheetName As String, _
299+
Optional RngName As String = "A1")
300+
Attribute DumpToSheet.VB_Description = "Dumps the CSV data from the current instance to an Excel Worksheet."
301+
Dim WBook As Workbook
302+
Dim OutputSheet As Worksheet
303+
Dim OutputRange As Range
304+
305+
On Error Resume Next
306+
If IsArrayAllocated(P_CSV_DATA) Then
307+
EnableOptimization
308+
'@------------------------------------------------------
309+
'Set the target Workbook
310+
If WBookName = vbNullString Then
311+
Set WBook = ThisWorkbook
312+
ElseIf Not IsWorkbookOpen(WBookName) Then
313+
Set WBook = Workbooks.Add
314+
Else
315+
Set WBook = Workbooks(WBookName)
316+
End If
317+
'@------------------------------------------------------
318+
'Set the target Worksheet
319+
If IsSheetInWorkbook(SheetName, WBook) Then
320+
Set OutputSheet = WBook.Sheets(SheetName)
321+
Else
322+
Set OutputSheet = WBook.Sheets.Add
323+
End If
324+
'@------------------------------------------------------
325+
'Set the target Range
326+
Set OutputRange = OutputSheet.Range(RngName) _
327+
.Resize _
328+
( _
329+
UBound(P_CSV_DATA, 1) - LBound(P_CSV_DATA, 1) + 1, _
330+
UBound(P_CSV_DATA, 2) - LBound(P_CSV_DATA, 2) + 1 _
331+
)
332+
'@------------------------------------------------------
333+
'Dump the data
334+
OutputRange.Value2 = P_CSV_DATA
335+
EnableOptimization False
336+
End If
337+
End Sub
338+
Private Sub EnableOptimization(Optional Optimize As Boolean = True)
339+
Attribute EnableOptimization.VB_Description = "Turn On and Off the optimized data dumping to an Excel Worksheet."
340+
If Optimize Then
341+
'@------------------------------------------------------
342+
'Optimize resource consumption
343+
Application.ScreenUpdating = False
344+
Application.Calculation = xlCalculationManual
345+
Application.EnableEvents = False
346+
Else
347+
'@------------------------------------------------------
348+
'Turn Off optimization
349+
Application.ScreenUpdating = True
350+
Application.Calculation = xlCalculationAutomatic
351+
Application.EnableEvents = True
352+
End If
353+
End Sub
296354
Public Sub ExportToCSV(csvArray As Variant)
297355
Attribute ExportToCSV.VB_Description = "Exports a 2D array to a CSV file located in the path specified in the OpenConnection method."
298356
On Error GoTo ErrHandler_ExportToCSV
@@ -597,6 +655,36 @@ Attribute IsANSI.VB_Description = "Verifies the charset for ANSI encoding."
597655
Erase bytFile
598656
IsANSI = (lngIndx > lngUprBnd)
599657
End Function
658+
Private Function IsArrayAllocated(ByRef arr() As String) As Boolean
659+
Attribute IsArrayAllocated.VB_Description = "Verifies if the given array is allocated on memory."
660+
Dim N As Long
661+
662+
On Error Resume Next
663+
N = UBound(arr, 1)
664+
If Err.number = 0 Then
665+
IsArrayAllocated = True
666+
Else
667+
IsArrayAllocated = False
668+
End If
669+
End Function
670+
Private Function IsSheetInWorkbook(SheetName As String, WBook As Workbook) As Boolean
671+
Attribute IsSheetInWorkbook.VB_Description = "Checks if the given sheet is part of the given or of the active one Workbook."
672+
With WBook
673+
On Error Resume Next
674+
IsSheetInWorkbook = (.Sheets(SheetName).Name = SheetName)
675+
On Error GoTo 0
676+
End With
677+
End Function
678+
Private Function IsWorkbookOpen(WBookName As String) As Boolean
679+
Attribute IsWorkbookOpen.VB_Description = "Checks if the given Workbook is opened yet."
680+
Dim WBook As Workbook, BookMatching As Boolean
681+
682+
On Error Resume Next
683+
For Each WBook In Workbooks
684+
BookMatching = (WBook.Name = WBookName)
685+
Next
686+
IsWorkbookOpen = BookMatching
687+
End Function
600688
Private Function JoinRecordsFields(RecordsArray As Variant) As String
601689
Attribute JoinRecordsFields.VB_Description = "Joins all fields for each record in the specified array."
602690
Dim buffer() As String

0 commit comments

Comments
 (0)