Enumerates and Sets and the Poor Man’s Unit Testing for VBA

By | April 18, 2011

VBUnit – The Poor Man's VBA Unit Testing Tool

Over the last few years I' got into unit testing in the Delphi environment. Its one of the reasons I developed the Integrated Testing Helper IDE add-in. Although I love Delphi language, I sometimes have cause to fall back on VBA in the office applications. I did a little searching on the internet to see if there were any DUnit, NUnit, JUnit equivalents for VB and VBA. I found a few but thought they were overly complicated in their implementation. So I thought, how hard can it be to do it myself.

All the code for this VBUnit can be within a single Module (not a class module) in VBA. The reason I’ve chosen a module, rather than a class module is that the code is very procedural, I don't have to create instances of classes and all the code can be encapsulated in a single module as opposed to modules and class modules.

You need reference to the Visual Basic for Application Extensibility library (C:\Program Files\Common Files\Microsoft Shared\VBA\VBA6\VBE6EXT.OLB) for this code to be able to automate the VBE IDE.

First I need to describe a number of private varaible of the module that keep track of various bits of information as the tests are being performed. They are as follows:

A private variable to hold the number of test passes.

Private FPasses As Long

A private variable to hold the number of test failures.

Private FFailures As Long

A private variable to hold the number of test errors.

Private FErrors As Long

A private constant to define the growth capacity of the message array.

Private Const iCAPACITY As Long = 100

A private array to hold the messages from the tests.

Private FMsgs() As String

A private variable to hold the current number of messages in the array.

Private FCount  As Long

A private variable to define if the project header has been printed.

Private FPrintProject As Boolean

A private variable to define if the module header has been printed.

Private FPrintModule As Boolean

A private variable to count the number of tests performed.

Private FTests As Long

A private variable to hold the last procedure name run.

Private FLastProcName As String

And private variable to the total processing time for the tests.

Private FTotalMS As Double

Because I want to time the tests (just because more of the other do this), I need to define a couple of declarations for the Performance Counter Win32API as follows:

Private Declare Function QueryPerformanceCounter Lib "kernel32" (lpPerformanceCount As Currency) As Long
Private Declare Function QueryPerformanceFrequency Lib "kernel32" (lpFrequency As Currency) As Long

Below is the Run method that starts the testing. In essence it searches the IDE for projects, then modules and then method to test as follows:

  • Iterate over all the project loading in the VBE IDE and process the ones that are not locked;
  • Iterate over each module in the above project;
  • For each module in the project get the procedure name for each line in the source code. Where this is not the same as the last procedure processed run the test.
Public Sub Run()
  Dim V As VBE
  Dim VP As VBProject
  Dim M As VBComponent
  Dim i As Long
  Dim strProcName As String
  Dim hnd As Long
  FTests = 0
  FPasses = 0
  FFailures = 0
  ReDim FMsgs(1 To iCAPACITY)
  FCount = 0
  FTotalMS = 0
  Set V = Application.VBE
  Debug.Print "Starting Unit Tests @ " & Format(Now, "ddd dd/mmm/yyyy hh:mm:ss")
  For Each VP In V.VBProjects
    If VP.Protection = vbext_pp_none Then
    FPrintProject = False
      For Each M In VP.VBComponents
        FPrintModule = False
        FLastProcName = ""
        For i = 1 To M.CodeModule.CountOfLines
          strProcName = M.CodeModule.ProcOfLine(i, vbext_pk_Proc)
          If strProcName <> FLastProcName Then
            RunTest strProcName, VP.Name, VP.Description, M.Name, M.Type
          End If
        Next
      Next M
    End If
  Next VP
  Debug.Print ""
  Debug.Print "Finished " & FTests & " Unit Tests, " & FPasses & " Pass(es), " & FFailures & _
    " Failure(s) and " & FErrors & " Error(s) (" & Format(FTotalMS, "#,##0.000") & " ms) @ " & Format(Now, "ddd dd/mmm/yyyy hh:mm:ss")
  Debug.Print ""
End Sub

The below method does the main work of running the test code. It should be noted here that since VBA does not have published method we can not identify the test methods in the same manner as DUnit. So I chose a simple method. All test modules must start their names with Test and all test methods must also start their names with Test.

This implementation allow for the use of the Setup and TearDown methods of DUnit. Each is run before and after each test respectively. The calls are wrapped in an error handler to capture errors and faults. You will have to make sure your VBA IDE options are set to “Break on Unhandled Errors”.

Also to note here is that all output information on the tests are output to the Immediates Window. This make it quite easy to both invoke and monitor the testing. Just type Run in the Immediates Windows and the test will start running.

The remaining code in the method is all about outputting information (headers, etc) and check that test have been performed and what their outcome was.

Private Sub RunTest(strProcName As String, strProjectName As String, strProjectDesc As String, _
  strModuleName As String, iModuleType As Long)
  Dim k As Long
  Dim strStatus As String
  Dim dblStart As Double
  Dim dblFinish As Double
  Dim j As Long
  Dim strTiming As String
  If strProcName Like "Test*" Then
    If Not FPrintProject Then
      Debug.Print "Project: " & strProjectName & " [" & strProjectDesc & "]"
      FPrintProject = True
    End If
    If Not FPrintModule Then
      Debug.Print "  " & strModuleName & " (" & ComponentType(iModuleType) & ")"
      FPrintModule = True
    End If
    FTests = FTests + 1
    k = FPasses + FFailures + FErrors
    dblStart = TickCount / 1000#
    On Error Resume Next
    Application.Run strModuleName & ".Setup"
    Application.Run strModuleName & "." & strProcName
    Application.Run strModuleName & ".TearDown"
    On Error GoTo 0
    dblFinish = TickCount / 1000#
    If FPasses + FFailures + FErrors = k Then
      AddMsg "      No checks performed!"
      FFailures = FFailures + 1
    End If
    If FCount = 0 Then strStatus = "OK    " Else strStatus = "Failed"
    strTiming = Format(dblFinish - dblStart, "#,##0.000")
    Debug.Print "    " & strModuleName & "." & strProcName & ", " & _
      String(60 - Len(strModuleName & "." & strProcName), " ") & strStatus & " (" & _
      String(12 - Len(strTiming), " ") & strTiming & " ms)"
    FTotalMS = FTotalMS + dblFinish - dblStart
    For j = 1 To FCount
      Debug.Print FMsgs(j)
    Next j
    ClearMsgs
    FLastProcName = strProcName
  End If
End Sub

The below code is a simple function to return the string representation of the ComponentType related to a VBA module.

Private Function ComponentType(iType As Long) As String
  Select Case iType
    Case vbext_ct_StdModule: ComponentType = "Standard module"
    Case vbext_ct_ClassModule: ComponentType = "Class module"
    Case vbext_ct_MSForm: ComponentType = "Microsoft Form"
    Case vbext_ct_ActiveXDesigner: ComponentType = "ActiveX Designer"
    Case vbext_ct_Document: ComponentType = "Document Module"
  Case Else
    ComponentType = "(Unknown)"
  End Select
End Function

The below piece of code is what does the checking. It contains an error handler to capture errors, so as described above you need to have you VBE IDE options set to “Break on Unhandled Errors”. If simply checks the 2 values and increments the failures or passes counters as appropriate.

Public Sub Check(varExpected As Variant, varActual As Variant, Optional strComment As String = "")
  On Error GoTo ErrHnd
  If varExpected <> varActual Then
    AddMsg "      Expected <" & varExpected & "> but was <" & varActual & ">. (" & strComment & ")"
    FFailures = FFailures + 1
  Else
    FPasses = FPasses + 1
  End If
ErrHnd:
  If Err.Number <> 0 Then
    FErrors = FErrors + 1
    AddMsg "      Error(" & Err.Number & "): " & Err.Description & " (" & strComment & ")"
  End If
End Sub

The below code simply adds a message to the message list. This is so more than one message can appear if errors occur in more than one check.

Private Sub AddMsg(strMsg As String)
  FCount = FCount + 1
  If FCount > UBound(FMsgs) Then
    ReDim Preserve FMsgs(1 To UBound(FMsgs) + iCAPACITY)
  End If
  FMsgs(FCount) = strMsg
End Sub

This method clears the message collection.

Private Sub ClearMsgs()
  FCount = 0
End Sub

Finally, this method calculates the time based on the declared performance counters above.

Private Function TickCount() As Double
  Dim C As Currency
  Dim f As Currency
  Dim dblC As Double
  Dim dblF As Double
  On Error GoTo ErrHnd
  QueryPerformanceCounter C
  QueryPerformanceFrequency f
  dblC = CDbl(C) * 10000#
  dblF = CDbl(f) * 10000#
  TickCount = 1000000# * dblC / dblF
ErrHnd:
  If Err.Number <> 0 Then MsgBox "TickTime: " & Err.Description
End Function

Implementing Tests

If your a good tester, you'll always write your tests before the actual method that need to be tested. You all do that don't you 🙂

Below are three tests for the three methods I need to have sets in VBA. I&#39ll go into the math in the next section while describing how sets work.

Sub TestInclude()
  Dim setMySet As Long
  setMySet = 0
  Include setMySet, 2
  Include setMySet, 3
  Check False, (setMySet And 2 ^ 1) <> 0, "Include 1"
  Check True, (setMySet And 2 ^ 2) <> 0, "Include 2"
  Check True, (setMySet And 2 ^ 3) <> 0, "Include 3"
  Check False, (setMySet And 2 ^ 4) <> 0, "Include 4"
  setMySet = 0
  Include setMySet, 2, 3
  Check False, (setMySet And 2 ^ 1) <> 0, "Include 1"
  Check True, (setMySet And 2 ^ 2) <> 0, "Include 2"
  Check True, (setMySet And 2 ^ 3) <> 0, "Include 3"
  Check False, (setMySet And 2 ^ 4) <> 0, "Include 4"
End Sub

Sub TestExclude()
  Dim setMySet As Long
  setMySet = 31
  Exclude setMySet, 2
  Exclude setMySet, 3
  Check True, (setMySet And 2 ^ 1) <> 0, "Exclude 1"
  Check False, (setMySet And 2 ^ 2) <> 0, "Exclude 2"
  Check False, (setMySet And 2 ^ 3) <> 0, "Exclude 3"
  Check True, (setMySet And 2 ^ 4) <> 0, "Exclude 4"
  setMySet = 31
  Exclude setMySet, 2, 3
  Check True, (setMySet And 2 ^ 1) <> 0, "Exclude 1"
  Check False, (setMySet And 2 ^ 2) <> 0, "Exclude 2"
  Check False, (setMySet And 2 ^ 3) <> 0, "Exclude 3"
  Check True, (setMySet And 2 ^ 4) <> 0, "Exclude 4"
End Sub

Sub TestInSet()
  Dim setMySet As Long
  setMySet = 12
  Check False, InSet(setMySet, 1), "Is 2 in 12"
  Check True, InSet(setMySet, 2), "Is 4 in 12"
  Check True, InSet(setMySet, 3), "Is 8 in 12"
  Check False, InSet(setMySet, 4), "Is 16 in 12"
  setMySet = 12
  Check False, InSet(setMySet, 1, 2), "Is 2 AND 4 in 12"
  Check True, InSet(setMySet, 2, 3), "Is 4 AND 8 in 12"
  Check False, InSet(setMySet, 3, 4), "Is 8 AND 16 in 12"
  Check False, InSet(setMySet, 4, 5), "Is 16 AND 32 in 12"
End Sub

Enumerates and Sets

One of the thing I love about the Object Pascal language is its enumerates and sets. Hopefully the Delphi users will know all about them but perhaps VB user don't, so I&#39ll explain.

Enumerates

Firstly I'll explain the Delphi version. In Delphi you can define an enumerate as below:

Type
  TMyEnumerate = (meFirst, meSecond, meThird, meFourth, meFifth);

By default the enumerates are equivalent to 1, 2, 3, 4 and 5 (you can number them specifically if you want). The difference between an enumerate and a constant is that in Delphi you can not interchange these without casting. Object Pascal is a very strongly typed language (which is another reason I like it) such that you can not interchange these enumerates with others, i.e. you can not pass a TMyEnumerate enumerate to a function expecting a TFontStyle enumerate.

In VBA, things are not so clearly defined. First off, we declare the above enumerate in VBA like this:

Enum TMyEnumerate
  meFirst
  meSecond
  meThird
  meFourth
  meFifth
End Enum

Again, these are associated with the integer numbers 1, 2, 3, 4 and 5. However, unlike Object Pascal, you can interchange integer numbers and enumerates in VBA code as the language is not so tightly typed.

Why do I use them? It makes the code easier to read as you can describe that the value is rather than just putting a number in. I like to use enumerate for boolean options in applications and sets as a way to manage those option. So lets now move onto Sets.

Sets

Sets are containers for ordinal types, one of which is enumerates. What this means is a set can contain zero, one, more or all integer numbers between a low and a high value. So in Object Pascal we would define a set as follows:

Type
  TMySet = Set Of TMyEnumerate;

Unfortunately, Visual Basic does not have a set construct in its language. So I've borrowed 2 ideas from pascal along with a third.

In Object Pascal you can add, remove and check the presence of a enumerate in a set as follows:

Include(MySet, myEnumerate);

Exclude(MySet, myEnumerate);

If myEnumerate In MySet Then
  Begin
  End;

So I've defined 3 methods in VBA as below:

Public Sub Include(ByRef setMySet As Long, ParamArray enumValues())
  Dim enumValue As Long
  Exception.Push "PrivateFunctions.Include", setMySet, enumValues
  On Error GoTo ErrHnd
  For enumValue = LBound(enumValues) To UBound(enumValues)
    setMySet = setMySet Or (2 ^ enumValues(enumValue))
  Next enumValue
ErrHnd:
  If Err.Number <> 0 Then Exception.DisplayErrorMessage Err
  Exception.Pop
End Sub
Public Sub Exclude(ByRef setMySet As Long, ParamArray enumValues())
  Dim enumValue As Long
  Exception.Push "PrivateFunctions.Exclude", setMySet, enumValues
  On Error GoTo ErrHnd
  For enumValue = LBound(enumValues) To UBound(enumValues)
    setMySet = setMySet And (&HFFFFFFFF - 2 ^ enumValues(enumValue))
  Next enumValue
ErrHnd:
  If Err.Number <> 0 Then Exception.DisplayErrorMessage Err
  Exception.Pop
End Sub
Public Function InSet(setMySet As Long, ParamArray enumValues()) As Boolean
  Dim enumValue As Long
  Exception.Push "PrivateFunctions.InSet", setMySet, enumValues
  On Error GoTo ErrHnd
  InSet = True
  For enumValue = LBound(enumValues) To UBound(enumValues)
    InSet = InSet And ((setMySet And 2 ^ enumValues(enumValue)) <> 0)
  Next enumValue
ErrHnd:
  If Err.Number <> 0 Then Exception.DisplayErrorMessage Err
  Exception.Pop
End Function

Ignore the Exception.Push() and Pop() calls and the error handling as these are not material to the code and are part of an exception handling and profiling frame work I use in my VBA applications.

Now we need some explanation as to what on earth is going on.

Sets are bit maps. No, not the pretty picture kind, but the original meaning of bit maps, i.e. the switching on or off of bits in a byte, word, double word, etc.

Lets consider a byte, which is made up of 8 bits. Assume we can switch on and off each bit independently. Now if we assign each bit for one of our enumerates (maximum of 8 in this case), one single byte can represent a set. My Include() and Exclude() routines switch on and off respectively their bits in the set, where as InSet() checks whether a bit is set or not. Obviously a word (2 bytes) can represent a set of 16 different enumerates.

I've coded my routines to be a little more flexibly than the pascal ones by allowing them to take more than one enumerate. However, note that VBA is not strictly typed, therefore there is no way to check that the enumerate you are adding or removing or checking is compatible with the set you are referencing.

Unfortunately, VBA doesn't allow the UBound() and LBound() method to work with enumerates so you can not iterate over the enumerates.

Hope this proves to be of interest to people.

regards
Dave.