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.

I am Mr. Forgetful. What was this password again?

Anyway, if you do not know any better, use brute force!

Source Code

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
' @Author - Alexander Bolte
' @ChangeDate - 2013-12-15
' @Description - Removes the password from a protected worksheet using brute force.
' Select a protected worksheet and start the sub.
Sub PasswordBreaker()
    Dim i As Integer, j As Integer, k As Integer
    Dim l As Integer, m As Integer, n As Integer
    Dim i1 As Integer, i2 As Integer, i3 As Integer
    Dim i4 As Integer, i5 As Integer, i6 As Integer
    Dim trg As Worksheet
  
    On Error Resume Next
  
    Set trg = ActiveSheet
  
    For i = 65 To 66: For j = 65 To 66: For k = 65 To 66
    For l = 65 To 66: For m = 65 To 66: For i1 = 65 To 66
    For i2 = 65 To 66: For i3 = 65 To 66: For i4 = 65 To 66
    For i5 = 65 To 66: For i6 = 65 To 66: For n = 32 To 126
        trg.Unprotect Chr(i) & Chr(j) & Chr(k) & _
            Chr(l) & Chr(m) & Chr(i1) & Chr(i2) & Chr(i3) & _
            Chr(i4) & Chr(i5) & Chr(i6) & Chr(n)
        If trg.ProtectContents = False Then
            MsgBox "One usable password is " & Chr(i) & Chr(j) & _
              Chr(k) & Chr(l) & Chr(m) & Chr(i1) & Chr(i2) & _
              Chr(i3) & Chr(i4) & Chr(i5) & Chr(i6) & Chr(n), vbInformation, ";0)"
            Exit Sub
        End If
    Next: Next: Next: Next: Next: Next
    Next: Next: Next: Next: Next: Next
End Sub

Saving an Excel workbook is a rather simple task. However you have to regard many things in IO operations, which can go wrong.

Therefore it is always good to  add some extra exception handling for IO operations that are likely to fail.

Hence, although saving a workbook requires only one line of code I use below method for saving workbooks.

Source Code

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
' @Author - Alexander Bolte
' @ChangeDate - 2014-10-26
' @Description - Saving handed workbook under provided path.
' @Param wrk - an initialized object of type Workbook.
' @Param trgPath - a String holding the target path the handed workbook to be saved to.
' @Returns - true, if the Workbook has been saved successfully, else false.
' @Remarks - the workbook is handed by reference. Therefore the calling function has to take care of closing it properly after has been saved.
' This function is only saving a handed workbook.
Public Function saveWorkbook(ByRef wrk As Workbook, ByVal trgPath As String) As Boolean
    Dim isSaved As Boolean
    
    On Error GoTo errHandle:
    
    wrk.SaveAs trgPath
    isSaved = True
    
errHandle:
    If Err.Number <> 0 Then
        Err.Clear
    End If
    
    saveWorkbook = isSaved
End Function 

In one of my projects I had to read all worksheet names from several Excel files.

Here is the code for getting all worksheet names from a closed or already opened Excel file.

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
' @Author - Alexander Bolte
' @Change Date - 26.12.2013
' @Description - Creates a list of all sheet names in workbook available under given file path.
' @Param filePath - Path to Microsoft Excel file the sheet name collection should be created from.
' @Returns - VBA.Collection holding all sheet names from given Microsoft Excel file.
Public Function getSheetNames(ByVal filePath As String) As VBA.Collection
    Dim wrk As Workbook
    Dim sheetNames As New VBA.Collection
    
    On Error GoTo errHandle:
    
    Set wrk = getOpenedWorkbook(filePath)
    If wrk Is Nothing Then
        Set wrk = Application.Workbooks.Open(filePath)
    End If
    ' Get the sheet names for one file.
    Set sheetNames = getSheetNamesFromWorkbook(wrk)
    ' Close workbook without saving.
    wrk.Close False
    
errHandle:
    If Err.Number <> 0 Then
        Err.Clear
    End If
    Set wrk = Nothing
    
    Set getSheetNames = sheetNames
End Function

Referenced Functions can be found below. 

getSheetNamesFromWorkbook(wrk)
Getting all sheet names from a workbook
getOpenedWorkbook(filePath)
Getting an opened Excel workbook