Replies: 2 comments 4 replies
-
Hi sancarn To be honest, I hadn't seen the library. I find the idea interesting, especially if I think about the usefulness that can be obtained in the field of routine testing. I would check and provide tested result soon! Edit: Edit 2: Add this method to the ''' <summary>
''' Returns an instance of the class holding the data from the specified CSV file.
''' The dialect can be automaticaly sniffed.
''' </summary>
''' <param name="csvFilePath">File to be loaded.</param>
''' <param name="sColumnName">Field to be readed.</param>
Public Function Create(csvFilePath As String, sColumnName As String) As CSVinterface
Dim oHelper As CSVinterface
Set oHelper = New CSVinterface
With oHelper
.parseConfig.path = csvFilePath
.parseConfig.delimitersGuessing = True
Set Create = .ImportFromCSV(.parseConfig, sColumnName)
End With
End Function Also add this method to the ''' <summary>
''' Returns the content from current instance to a two-dimensional array
''' using a list of indices.
''' </summary>
''' <param name="StartIndex">The index in which the operation will start.</param>
''' <param name="EndIndex">The index in which the operation will end.</param>
Public Function CopyToArray2(arrIndices() As Variant) As Variant()
Dim c As Long
Dim arrLB As Long
Dim arrUB As Long
Dim tmpResult() As Variant
Dim tArr() As Variant
arrLB = LBound(arrIndices)
arrUB = UBound(arrIndices)
ReDim tmpResult(0 To arrUB - arrLB)
If Not P_INDEXING Then
For c = 0 To arrUB - arrLB
tmpResult(c) = Buffer(arrIndices(arrLB + c))
Next c
Else
For c = 0 To arrUB - arrLB
If Not P_KEYS_TREE Then
tmpResult(c) = IndexedBuffer(arrIndices(arrLB + c)).ItemValue
Else
tmpResult(c) = IndexedBuffer(arrIndices(arrLB + c)).ITree.items
End If
Next c
End If
JaggedToTwoDimArray tmpResult, tArr
CopyToArray2 = tArr
End Function Now we can test the solution with Private Sub testGetRandomCSVSetOfData()
Dim csv As CSVinterface
Dim i As Long
Dim randomIndices() As Variant
Dim tmpData() As Variant
Set csv = New CSVinterface
With stdPerformance.Measure("#1 Load CSV data to menory")
Set csv = csv.Create("C:\csv's\Demo_50k_records.csv", "Order_Date") 'Load a 50k records CSV
End With
ReDim randomIndices(0 To 1999)
For i = 0 To UBound(randomIndices)
randomIndices(i) = Int(2 + Rnd() * (50000))
Next i
With stdPerformance.Measure("#2 Copy 2000 records of CSV data to a two-dimentional array")
tmpData() = csv.items.CopyToArray2(randomIndices) 'Copy and transform to 2D array
End With
Set csv = Nothing
End Sub On my PC I get the following result #1 Load CSV data to menory: 1828 ms
#2 Copy 2000 records of CSV data to a two-dimentional array: 0 ms |
Beta Was this translation helpful? Give feedback.
-
This has been implemented in sancarn/xlMocker#1 |
Beta Was this translation helpful? Give feedback.
-
Hi Garcia,
Not sure if you've seen, but I'm creating a mock data generator. The idea is to use UDFs to generate datasets. For example:
I have an existing function
mockCalc_ValueFromRange
implemented as follows:I.E. given a range, it will randomly select
iNumber
values, and return an array of these values.I'm looking to add a
mockCalc_ValueFromCSV
function, something like (pseudo-code):I realise this is highly specific, but want this to be as optimal as possible. How geared up for this task would this library be, and how would you go about it?
Beta Was this translation helpful? Give feedback.
All reactions