Excel VBA

This category will hold articles regarding developement in Excel VBA. It will serve as a wiki and an Excel VBA Framework for myself.

Some development tasks reoccur for every customer. Since I am a lazy bum it will be nice to have a central source where I can reuse source code from.

Excels behaviour can be quite annoying from time to time. One prime example is adjusting the row height of merged cells.

Normally you would think you can adjust the row height of a merged area the same way you adjust it for single cells.

Nope! No matter what you try it will not work properly.

However, below method can solve this issue partly for you. It will adjust the row height for a handed merged range of cells, but it only works for merged cells in one row. So, feel free to adjust this function to your needs and don't forget to share it with those who are in need ;0).

Source Code

' @Author - Alexander Bolte
' @Description - Adjusting the row height to content similar to Excel standard function for wrapping cell content.
' This method only works for merged cells accross one row.
' @Param rng - a Range object referencing a merged area.
Public Sub adjustRowHeightOfMergedCells(ByRef rng As Range)
Dim mergedWidth As Variant
Dim firstCell As Range
Dim newHeight As Double

If rng.MergeCells Then
mergedWidth = getColumnWidth(rng)
rng.MergeCells = False
Set firstCell = rng.Cells(1, 1)
firstCell.Columns.ColumnWidth = mergedWidth
firstCell.WrapText = True
firstCell.EntireRow.AutoFit
newHeight = firstCell.EntireRow.Height
rng.MergeCells = True
rng.Columns.ColumnWidth = (mergedWidth / rng.Columns.Count)
' Only adjust a rows height, if the current row height is smaller
' than the new height needed to display merged cells content properly.
If rng.Rows.EntireRow.RowHeight < newHeight Then
rng.Rows.EntireRow.RowHeight = newHeight
End If
End If
End Sub

Ok, now that we can adjust the row height of merged cells in Excel VBA, we have one question to answer.

How do I find merged cells?

The answer can be found in the source code below.

' @Author - Alexander Bolte
' @Description - Running through the columns of the handed range's parent worksheet used range,
' checking each cell in the first row of handed range for a valid MergedArea attribute
' and then returning the MergedArea.
' @Param srcRow - a Range object referencing a row in an Excel worksheet.
' @Param startCol - an Integer providing the start column from which a search for merged cells should begin.
Public Function getMergedCells(ByRef srcRow As Range, ByVal startCol As Integer) As Range
Dim ws As Worksheet
Dim testCell As Range
Dim merged As Range
Dim i As Integer

Set ws = srcRow.Parent
For i = startCol To ws.UsedRange.Columns.Count
Set testCell = ws.Cells(srcRow.Row, i)
Set merged = testCell.MergeArea
If merged.Columns.Count > 1 Then
Exit For
Else
Set merged = Nothing
End If
Next i

Set getMergedCells = merged
End Function

And how can you put both together? I prefer a method that uses recursion to run through the different columns in a given row but you can also run iteratively through the columns.

' @Author - Aleaxander Bolte
' @Description - Running recursively through an Excel row, adjusting the row height to all merged cells content, if the row height is not already greater than the new row height.
' @Param ws - a Worksheet object the change should be applied on.
' @Param trgRow - the target row the change should be applied on.
Private Sub adjustRowHeightToContent(ByRef ws As Worksheet, ByVal trgRow As Long)
Dim merged As Range

Set merged = xReusableCode.getMergedCells(ws.Rows(trgRow), 1)
' Stop condition for recursion.
If Not (merged Is Nothing) Then
' Adjust row height of merged cells.
Call adjustRowHeightOfMergedCells(merged)
' Call recursively.
Call adjustRowHeightToContent(ws, merged.Column + merged.Columns.Count - 1)
End If
End Sub

There you go, all done. Hope it helps, even if you only get a hint on how to do it yourself.

If you need to reference a workbook, which might already be opened but all you have ready is the file path the following function will do the trick for you.

If the Excel workbook is not opened oran opened workbook with the same name is not saved under given file path, Nothing will be returned.

' @Author - Alexander Bolte
' @Change Date - 2013-12
' @Description - Returns a workbook object referencing an Excel file
' available under given file path, if the Excel file was already opened before calling this function.
' @Param filePath - a path to an Excel file.
' @Returns - a workbook object referencing an Excel file available under given file path.
Public Function getOpenedWorkbook(ByVal filePath As String) As Workbook
Dim ret As Workbook
Dim wrkName As String
Dim sep As String
Dim splitted() As String

On Error GoTo errHandle:

' Get the separator for path strings on operating system.
sep = Application.PathSeparator
splitted = Split(filePath, sep)
wrkName = splitted(UBound(splitted))
Set ret = Application.Workbooks(wrkName)
If ret.path <> filePath Then
ret = Nothing
End If

errHandle:
If Err.Number <> 0 Then
Err.Clear
End If

Set getOpenedWorkbook = ret
End Function

Whenever I have to apply more complex  text operations I tend to use regular expressions.

If you want to remove HTML tags from a String, nothing is faster and easier than using regular expressions to do so.

Source Code

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
' @Author - Alexander Bolte
' @ChangeDate - 2014-11-06
' @Description - Removing HTML tags from a provided HTML text.
' @Param htmlText - a String holding HTML text.
' @Remarks - Using a regular expression to remove HTML tags from a provided String.
' Regular expression is as follows.
' "<([A-Z][A-Z0-9]*)\b[^>]*>|<\/([A-Z][A-Z0-9]*)>"
Public Function replaceHTMLTags(ByVal htmlText As String) As String
    Dim regEx As New RegExp
    Const cHtmlPattern As String = "<([A-Z][A-Z0-9]*)\b[^>]*>|<\/([A-Z][A-Z0-9]*)>"
    
    regEx.Global = True
    regEx.IgnoreCase = True
    regEx.pattern = cHtmlPattern
    htmlText = regEx.Replace(htmlText, "")
    
    replaceHTMLTags = htmlText
End Function

Referenced APIs

This code references the following API, which is a VBScript API.

"Microsoft VBScript Regular Expression Reference 5.5"

In order to reference this API in Excel VBA go to Options -> References (In German "Extras" -> "Verweise") and tick the API above.