Customize Headers in a Large Table using Excel VBA
This instruction will guide you on how to build a table with customized pattern table headers.
Table of contents
- Purpose of this instruction
- Enable Developer Tab in Excel
- Create a module in VBA
- Implement the row & column label macros in the spreadsheet
- How to use the macro
- Benefits of using macro
Purpose of this instruction
Sometimes you will need to build a very large table with atypical column and/or row labels. Each label corresponds to an item in real world, such as a specimen, case number, or a serial number in increasing order. Excel’s built-in autofill function may not recognize the pattern of the labels. Instead of manually entering the names of each column or row, it is easier to use VBA to generate the row and column labels for us. This macros introduced in this guide can serve as a reusable table builder template.
NOTE: Excel’s row and column limits are 1048576 and 16384 respectively. You cannot build a table with row count greater than 1048576 and column count greater than 16384.
Enable Developer Tab in Excel
NOTE: Web-based version of Excel does not support VBA. You must use an installed version of Microsoft Excel to proceed with this instruction.
If your Microsoft Excel already has developer mode enabled, skip to Create a module in VBA.
Windows
Open Microsoft Excel and open a blank workbook. Save this workbook in your preferred location and select file type as Excel Macro-Enabled Workbook (*.xlsm)
WARNING: Saving the file as regular Excel workbook (.xlsx) will result in the loss of ALL VBA codes!
Go to [File] > [Options].
This opens the Excel Options window.
- Click Customize Ribbon on the sidebar at the left side to enter
Check the box labeled Developer. Click OK to save and exit.
You should see a new tab named Developer at the ribbon located at the top.
Create a module in VBA
A VBA module is where you can create and save functions. Developers use modules to group related functions together.
Go to [Developer] > [Visual Basic] to open VBA Integrated Development Environment.
Insert a new module by going to [Insert] > [Module]. A new module named Module1 appears in the Modules folder in the [Project] window.
Double click on Module1. Change the name of the module by going to the [Properties] window, and replace the name with CustomRowColumnLabels.
NOTE: Module names cannot contain spaces and cannot begin with a numeric character or symbols.
In the VBA editor window, paste the following codes.
Sub createRowLabels()
Dim prefix, postfix As String
prefix = getPrefix
postfix = getPostfix
Dim idStr As String: idStr = getId
Dim idNumeric As Long
If IsNumeric(id) Then
idNumeric = CInt(idStr)
Else
MsgBox ("id is not a number")
Exit Sub
End If
Dim countStr As String: countStr = getCount
Dim countNumeric As String
If IsNumeric(countStr) Then
countNumeric = CInt(countStr)
Else
MsgBox ("number of rows must be a number")
Exit Sub
End If
Dim rowCount As Integer: rowCount = 2
For i = 1 To countNumeric
ThisWorkbook.Sheets(1).Range("A" & rowCount).Value = prefix & idNumeric & postfix
rowCount = rowCount + 1
idNumeric = idNumeric + 1
Next i
End Sub
Sub createColumnLabels()
Dim prefix, postfix As String
prefix = getPrefix
postfix = getPostfix
Dim idStr As String: idStr = getId
Dim idNumeric As Long
If IsNumeric(id) Then
idNumeric = CInt(idStr)
Else
MsgBox ("id is not a number")
Exit Sub
End If
Dim countStr As String: countStr = getCount
Dim countNumeric As String
If IsNumeric(countStr) Then
countNumeric = CInt(countStr)
Else
MsgBox ("number of rows must be a number")
Exit Sub
End If
Dim ColumnCount As Integer: ColumnCount = 2
For i = 1 To countNumeric
ThisWorkbook.Sheets(1).Cells(1, ColumnCount).Value = prefix & idNumeric & postfix
ColumnCount = ColumnCount + 1
idNumeric = idNumeric + 1
Next i
End Sub
Function getPrefix() As String
getPrefix = InputBox("Enter prefix", "Please enter the prefix (Leave empty if none)")
End Function
Function getPostfix() As String
getPostfix = InputBox("Enter postfix", "Please enter the postfix (Leave empty if none)")
End Function
Function getId() As String
getId = InputBox("Enter starting number", "Please enter the starting number")
End Function
Function getCount() As String
getCount = InputBox("Enter number of items to create", "Please enter the number of items to create")
End Function
Function getNewTabName() As String
getNewTabName = InputBox("Enter the name of new tab", "Please enter the name of the new tab")
End Function
Here is a screenshot snippet of how the VBA editor should look like.
Implement the row & column label macros in the spreadsheet
The fastest method is to add buttons and mapped them to the macros we created above.
Go to [Developer] > [Insert] > [Form Controls] > Button.
Left-click and drag a small distance to create a new button.
An Assign Macro window appears to connect the macro to this button.
- Assign the createColumnLabels macro by double clicking on it.
- Rename Button 1 to a different name by right-clicking on it, and edit the text inside the button
- Repeat steps 1, 2, and 3 above to implement the row label macro.
How to use the macro
Activate the create column labels macro by click on the button named after it.
Enter the prefix in the message box titled Please enter the prefix (Leave empty if none). Click OK to continue.
Enter the postfix in the message box titled Please enter the postfix (Leave empty if none). Click OK to continue.
Enter the first number in the series of columns in the message box titled Please enter the starting number.
You must enter a integer number and cannot leave this box empty. Click OK to continue.
Enter the number of columns to create in the message box titled Please enter the number of rows to create.
You must enter a integer number and cannot leave this box empty. Click OK to continue.
Excel will generate the column labels based on the information you entered. Below is an example of a table created using the macro above.
Congratulation! You have learned how to use a macro to auto-populate row and column headers.
Benefits of using macro
You can save a lot of time by using macro to automate tasks and avoid human error from manual entry.