In a recent Mr Excel post, a member asked how to convert a CSV File to Excel File with Dynamic Graphing Capability. This is a great topic for a tutorial, but too long for a forum answer.
Problem Statement
The simple statement was this:
- Convert a CSV file to an Excel workbook
- Create a chart based on
- User-specified chart type
- User-specified columns for X and Y
I expanded on this a little bit:
- Open a user-selected CSV file
- Save as an Excel workbook
- Display dialog for user to select
- Chart type
- Columns containing X and Y values for chart
- Create the desired chart
This is a pretty easy project, which would generally take me half a day or less, depending on other distractions.
Approach
Essentially, I started with this simple VBA procedure, and a similarly simple UserForm (dialog).
Sub OpenCSVFileAndPlotData()
' 1. Get CSV file name
' 2. Open CSV file
' 3. Save as workbook
' 4. Parse file
' 5. Show dialog (select chart type, X values, Y values)
' 6. Draw chart
' 7. Save file
End Sub
My first time through development, I did the least I had to do to make it work. The second time through, I added a bunch of nice embellishments that should make things easier for users to just pick it up and run with it.
For both levels, the following sections have pieces of code describing what is happening, the complete code, and an example workbook.
Building a Simple Solution
Code Workbook
I’m using a macro-enabled Excel workbook named My_CSV_Data_Processor.xlsm. It has a single worksheet named Parameters.
Saved Information: Named Range Containing Chart Types
The worksheet contains a list of chart types that our program will create. These are the simplest and most useful charts built into Excel. The list has two columns, the first being the integer values of Excel’s chart type constants (e.g., xlArea
= 1, xlXYScatter
= -4169), the second being the chart type names that will appear in the dialog.
The range A2:B12 has been named ChartTypes, so it will be easy for the code to put these values into the dialog.
Starting the Program: Form Control Button
To add a button, the Developer tab must be visible on the ribbon. If you don’t see it, right-click on a blank place in the ribbon, choose Customize the Ribbon. In the list on the right (Main Tabs), click the box in front of Developer.
On the Developer tab, in the Controls group, click the Insert dropdown, then under Form Controls, click on the first icon, Button. Draw a button on the worksheet.
A dialog will pop up asking which VBA procedure to assign to the button; you can revisit this dialog by right-clicking on the button. Select OpenCSVFileAndPlotData and press OK. Then type a caption on the button and resize it as needed.
Code Module
We need to put the code into a regular code module. In the VB Editor, find the workbook’s project in the Project Explorer pane, right click anywhere on it, and choose Insert > Module. When a new code module opens up in the editor, rename it to something useful like MChartFromCSVFile using the Properties pane. The exact name you use isn’t critical, but it should be somewhat descriptive.
On the View menu, click Project Explorer (Ctrl+R) or Properties (F4) if these panes are not visible.
Getting Ready
The first line of the module should be
Option Explicit
If this statement doesn’t appear, type it in, then go to Tools menu > Options, and check the Require Variable Declaration box. While you’re in the Options dialog, uncheck Auto Syntax Check.
After a blank line or two, type Sub and the name of the procedure. The VB Editor automatically skips another line and types End Sub for you:
Sub OpenCSVFileAndPlotData()
End Sub
The main program will be typed between Sub and End Sub. All the variables will be declared at the top using Dim statements. Variables don’t need to be declared at the top of a routine, but VBA offers no just-in-time benefit to declaring them right where you start using them, and I like having them in one place so I can find their declarations easily. In the sections below I will insert a simple Dim statement for the variables used.
1. Get CSV File Name
We can use Excel’s GetOpenFileName to allow the user to select a CSV file from his computer.
Dim sCSVFullName As String
sCSVFullName = Application.GetOpenFilename("CSV Files (*.csv), *.csv", , _
"Select a CSV file", , False)
We’ve specified the CSV file filter, indicated a title for the Open File dialog, and said False to selecting multiple files.
2. Open CSV file
This part is easy, we just need to open the file named in the previous step. Then we’ll set a workbook object variable to this file, so it’s easy to reference later in the code.
Dim wb As Workbook
Workbooks.Open sCSVFullName
Set wb = ActiveWorkbook
3. Save as workbook
We need to remove the file extension from the CSV file name (which includes the file path), which we do by retaining only text up to the last period in the file name. Then we add the Excel workbook file extension, and save the file, specifying the default workbook format.
Dim sWbkFullName As String, sFileRoot As String
sFileRoot = Left$(sCSVFullName, InStrRev(sCSVFullName, ".") - 1)
sWbkFullName = sFileRoot & ".xlsx"
wb.SaveAs sWbkFullName, xlWorkbookDefault
4. Parse file
Now the file is open, so we’ll extract some information to place in the dialog. We’ll use a two-column display, where the first column has the column number, and the second a simple comma-delimited list of the first few values in that column.
Dim ws As Worksheet, rng As Range, vRng As Variant
Dim iRows As Long, iCols As Long, iRow As Long, iCol As Long
Dim sTemp As String
Dim vChartData As Variant
Set ws = wb.Worksheets(1)
Set rng = ws.UsedRange
vRng = rng.Value2
iRows = rng.Rows.Count
iCols = rng.Columns.Count
'' info to display: column number, first few rows of column
ReDim vChartData(1 To iCols, 1 To 2)
For iCol = 1 To iCols
vChartData(iCol, 1) = iCol ' column number
sTemp = ""
For iRow = 1 To 4 ' first 4 values
sTemp = sTemp & vRng(iRow, iCol) & ", "
Next
sTemp = Left$(sTemp, Len(sTemp) - 2) ' remove last comma
vChartData(iCol, 2) = sTemp
Next
5. Show dialog
We need to instantiate the UserForm (i.e., load it into memory), pass in the array of column numbers and initial column values, and display the form. At this point, code stops and waits for the user to make his selections and dismiss the form.
When the form is dismissed, we need to get the user’s selections: chart type, whether the CSV file has header labels in the first row, and the columns to be used for X and Y values in the chart. Then we remove the UserForm from memory.
Dim bFirstRowHeaders As Boolean
Dim myChartType As XlChartType
Dim vX As Variant, vY As Variant
Dim frmChartFromCSVFile As FChartFromCSVFile
Set frmChartFromCSVFile = New FChartFromCSVFile
With frmChartFromCSVFile
'' pass in information we know
.ChartData = vChartData
.Show
'' get information selected by user
myChartType = .ChartType
bFirstRowHeaders = .FirstRowHeaders
vX = .Xcolumns
vY = .YColumns
End With
Unload frmChartFromCSVFile
6. Draw chart
We need to figure out how to separate the data into separate series, then we need to get the data into the chart.
In XY charts, we let the user create one or more series, where (a) all series share the same set of X values (or no X values if the user didn’t specify them, and Excel will use 1, 2, 3, etc. as X values) and each series has a unique set of Y values, (b) all series share the same set of Y values and each has a unique set of X values, or (c) each series has its own unique sets of X and Y values.
For other chart types, the only relevant combination of X and Y is (a), since Excel uses the same X values for all series regardless of how we specify them. We will deal with this in the Advanced version of this program.
Excel 2013 introduced AddChart2 as an improvement over Excel 2007’s AddChart method. AddChart is hidden in Excel 2013, but AddChart2 will crash Excel 2007 and 2010, so we will use AddChart. In the Advanced program, we will enhance the code to use Excel 2013’s improved default styles while still using the error-free AddChart method.
After adding the chart, we add one series at a time, adding its Y values, X values, and name separately.
Dim iX As Long, iY As Long, iSrs As Long
Dim nX As Long, nY As Long, nSrs As Long
Dim rCht As Range, cht As Chart, srs As Series
'' define some series parameters
If IsEmpty(vX) Then
nX = 0
Else
nX = UBound(vX, 1) + 1 - LBound(vX, 1)
End If
nY = UBound(vY, 1) + 1 - LBound(vY, 1)
nSrs = nY
If nX > nY Then nSrs = nX
If bFirstRowHeaders Then
Set rCht = rng.Offset(1).Resize(iRows - 1)
Else
Set rCht = rng
End If
'' select blank cell before inserting chart
rng.Offset(iRows + 1, iCols + 1).Resize(1, 1).Select
Set cht = ws.Shapes.AddChart.Chart '' Excel 2007+
'' chart type
With cht
If myChartType <> 0 Then
.ChartType = myChartType
End If
'' add series
For iSrs = 1 To nSrs
Set srs = .SeriesCollection.NewSeries
With srs
' X values
If nX = 0 Then
' no X values specified
ElseIf nX = 1 Then
' all series share X values
.XValues = rCht.Columns(CLng(vX(0, 0)))
Else
' each series has unique X values
.XValues = rCht.Columns(CLng(vX(iSrs - 1, 0)))
End If
' Y values
If nY = 1 Then
' all series share Y values
.Values = rCht.Columns(CLng(vY(0, 0)))
Else
' each series has unique Y values
.Values = rCht.Columns(CLng(vY(iSrs - 1, 0)))
End If
' series name
If bFirstRowHeaders Then
If nSrs = nY Then
.Name = "=" & rng.Cells(1, CLng(vY(iSrs - 1, 0))). _
Address(True, True, xlA1, True)
ElseIf nSrs = nX Then
.Name = "=" & rng.Cells(1, CLng(vX(iSrs - 1, 0))). _
Address(True, True, xlA1, True)
End If
End If
End With
Next
End With
7. Save file
Simple: save changes.
wb.Save
UserForm
Right click on the workbook’s project in the Project Explorer pane, click Insert > UserForm. When the UserForm appears, give it the name FChartFromCSVFile in the properties pane. This name is descriptive, and is how your code references the UserForm.
UserForm Controls
The Userform contains the following important controls, with the important properties shown below:
btnOK – OK button
Default: True
lstChartType – Listbox with two columns, one hidden.
ColumnCount: 2
ColumnWidths: 0 pt;112 pt
Width: 120
Height: 150
lstChartData – Listbox with two columns, extended multiselect
ColumnCount: 2
ColumnWidths: 42 pt;145 pt
Width: 195
Height: 150
MultiSelect: 2 - fmMultiSelectExtended
lstX, lstY – simple listboxes
lblbtnX, lblbtnY, lblbtnReset – “Label Buttons” or Labels with raised appearance (like regular buttons)
SpecialEffect: 1 - fmSpecialEffectRaised
chkFirstRowHeaders – Checkbox
Plus a few labels that help the user understand the dialog.
UserForm Code
Right click on the UserForm in the Project Explorer, and click on View Code. The Dialog’s code module will appear. Much of this code responds to events on the UserForm, events like clicking buttons. This code also includes properties, which allow the calling procedure to pass information into the UserForm and get information back from it.
As with the regular code module, the UserForm module should begin with
Option Explicit
If a control on the UserForm is to have code associated with it, double-click on the control and the VB Editor will insert a short stub of code into the module. For example, if you double-click on the OK button (named btnOK), the Editor will insert this:
Private Sub btnOK_Click()
End Sub
To make the code useful, we only need to insert our statements within this stub.
When the user clicks the OK button, we want the form to be hidden but remain in memory:
Private Sub btnOK_Click()
Me.Hide
End Sub
When the UserForm is first loaded, we want the information from the named range ChartTypes to appear in the listbox lstChartTypes. The UserForm_Initialize code runs when the UserForm is loaded, and the code shown here does the magic:
Private Sub UserForm_Initialize()
Dim vChartTypes As Variant
vChartTypes = ThisWorkbook.Names("ChartTypes").RefersToRange.Value2
Me.lstChartTypes.List = vChartTypes
End Sub
The button-formatted labels need some simple code attached, so that clicking them will populate the X and Y column lists. Click the lblbtnX label button to populate the lstX listbox:
Private Sub lblbtnX_Click()
Dim iLst As Long
For iLst = 1 To Me.lstChartData.ListCount
If Me.lstChartData.Selected(iLst - 1) Then
Me.lstX.AddItem iLst
End If
Next
End Sub
Click the lblbtnY label button to populate the lstY listbox:
Private Sub lblbtnY_Click()
Dim iLst As Long
For iLst = 1 To Me.lstChartData.ListCount
If Me.lstChartData.Selected(iLst - 1) Then
Me.lstY.AddItem iLst
End If
Next
End Sub
Click the lblbtnReset lable button to clear the X and Y listboxes and start over:
Private Sub lblbtnReset_Click()
Me.lstX.Clear
Me.lstY.Clear
End Sub
We need the ChartData property to pass the information to display in the lstChartData listbox of the UserForm:
Public Property Let ChartData(vData As Variant)
Me.lstChartData.List = vData
End Property
We also needproperties to let us extract information from the UserForm: whether the first row of the CSV file has header labels, the selected chart type, and the X and Y columns to be plotted:
Property Get FirstRowHeaders() As Boolean
FirstRowHeaders = Me.chkFirstRowHeaders.Value
End Property
Public Property Get ChartType() As XlChartType
With Me.lstChartTypes
If .ListIndex > -1 Then
ChartType = CLng(.List(.ListIndex, 0))
End If
End With
End Property
Public Property Get Xcolumns() As Variant
Xcolumns = Me.lstX.List
End Property
Public Property Get YColumns() As Variant
YColumns = Me.lstY.List
End Property
The Simple Tool
Code Module MChartFromCSVFile
Here is the complete listing of MChartFromCSVFile:
Option Explicit
Sub OpenCSVFileAndPlotData()
Dim sCSVFullName As String, sWbkFullName As String, sFileRoot As String
Dim wb As Workbook, ws As Worksheet, rng As Range, vRng As Variant
Dim rCht As Range, cht As Chart, srs As Series
Dim iRows As Long, iCols As Long, iRow As Long, iCol As Long
Dim sTemp As String
Dim vChartData As Variant
Dim bFirstRowHeaders As Boolean
Dim myChartType As XlChartType
Dim vX As Variant, vY As Variant
Dim iX As Long, iY As Long, iSrs As Long
Dim nX As Long, nY As Long, nSrs As Long
Dim frmChartFromCSVFile As FChartFromCSVFile
' 1. Get CSV file name
sCSVFullName = Application.GetOpenFilename("CSV Files (*.csv), *.csv", , _
"Select a CSV file", , False)
' 2. Open CSV file
Workbooks.Open sCSVFullName
Set wb = ActiveWorkbook
' 3. Save as workbook
sFileRoot = Left$(sCSVFullName, InStrRev(sCSVFullName, ".") - 1)
sWbkFullName = sFileRoot & ".xlsx"
wb.SaveAs sWbkFullName, xlWorkbookDefault
' 4. Parse file
Set ws = wb.Worksheets(1)
Set rng = ws.UsedRange
vRng = rng.Value2
iRows = rng.Rows.Count
iCols = rng.Columns.Count
'' info to display: column number, first few rows of column
ReDim vChartData(1 To iCols, 1 To 2)
For iCol = 1 To iCols
vChartData(iCol, 1) = iCol
sTemp = ""
For iRow = 1 To 4
If iRow > iRows Then Exit For
sTemp = sTemp & vRng(iRow, iCol) & ", "
Next
sTemp = Left$(sTemp, Len(sTemp) - 2)
vChartData(iCol, 2) = sTemp
Next
' 5. Show dialog (get chart type, X values, Y values)
Set frmChartFromCSVFile = New FChartFromCSVFile
With frmChartFromCSVFile
'' pass in information we know
.ChartData = vChartData
.Show
myChartType = .ChartType
bFirstRowHeaders = .FirstRowHeaders
vX = .Xcolumns
vY = .YColumns
End With
Unload frmChartFromCSVFile
' 6. Draw chart
'' define some series parameters
If IsEmpty(vX) Then
nX = 0
Else
nX = UBound(vX, 1) + 1 - LBound(vX, 1)
End If
nY = UBound(vY, 1) + 1 - LBound(vY, 1)
nSrs = nY
If nX > nY Then nSrs = nX
If bFirstRowHeaders Then
Set rCht = rng.Offset(1).Resize(iRows - 1)
Else
Set rCht = rng
End If
'' select blank cell before inserting chart
rng.Offset(iRows + 1, iCols + 1).Resize(1, 1).Select
Set cht = ws.Shapes.AddChart.Chart '' Excel 2007+
''Set cht = ws.Shapes.AddChart2.Chart '' Excel 2013 only
'' chart type
With cht
.ChartType = myChartType
'' add series
For iSrs = 1 To nSrs
Set srs = .SeriesCollection.NewSeries
With srs
' X values
If nX = 0 Then
' no X values specified
ElseIf nX = 1 Then
' all series share X values
.XValues = rCht.Columns(CLng(vX(0, 0)))
Else
' each series has unique X values
.XValues = rCht.Columns(CLng(vX(iSrs - 1, 0)))
End If
' Y values
If nY = 1 Then
' all series share Y values
.Values = rCht.Columns(CLng(vY(0, 0)))
Else
' each series has unique Y values
.Values = rCht.Columns(CLng(vY(iSrs - 1, 0)))
End If
' series name
If bFirstRowHeaders Then
If nSrs = nY Then
.Name = "=" & rng.Cells(1, CLng(vY(iSrs - 1, 0))). _
Address(True, True, xlA1, True)
ElseIf nSrs = nX Then
.Name = "=" & rng.Cells(1, CLng(vX(iSrs - 1, 0))). _
Address(True, True, xlA1, True)
End If
End If
End With
Next
End With
' 7. Save file
wb.Save
ExitProcedure:
End Sub
UserForm Module FChartFromCSVFile
Here is the complete listing of FChartFromCSVFile:
Option Explicit
Private Sub btnOK_Click()
Me.Hide
End Sub
Private Sub lblbtnReset_Click()
Me.lstX.Clear
Me.lstY.Clear
End Sub
Private Sub lblbtnX_Click()
Dim iLst As Long
For iLst = 1 To Me.lstChartData.ListCount
If Me.lstChartData.Selected(iLst - 1) Then
Me.lstX.AddItem iLst
End If
Next
End Sub
Private Sub lblbtnY_Click()
Dim iLst As Long
For iLst = 1 To Me.lstChartData.ListCount
If Me.lstChartData.Selected(iLst - 1) Then
Me.lstY.AddItem iLst
End If
Next
End Sub
Public Property Let ChartData(vData As Variant)
Me.lstChartData.List = vData
End Property
Property Get FirstRowHeaders() As Boolean
FirstRowHeaders = Me.chkFirstRowHeaders.Value
End Property
Public Property Get ChartType() As XlChartType
With Me.lstChartTypes
If .ListIndex > -1 Then
ChartType = CLng(.List(.ListIndex, 0))
End If
End With
End Property
Public Property Get Xcolumns() As Variant
Xcolumns = Me.lstX.List
End Property
Public Property Get YColumns() As Variant
YColumns = Me.lstY.List
End Property
Private Sub UserForm_Initialize()
Dim vChartTypes As Variant
vChartTypes = ThisWorkbook.Names("ChartTypes").RefersToRange.Value2
Me.lstChartTypes.List = vChartTypes
End Sub
Workbook with Working Code
You can download the simple workbook My_CSV_Data_Processor.xlsm to see all of this code in one place, and to see how it works.
Advanced Version
The next blog post has a number of enhancements that make things easier for the user and prevent various warning messages: VBA: An Advanced Add-in to Open a CSV File and Create Chart with Data Specified by User.