UserForm1.Show

I’ve seen these tutorials. You’ve probably seen them too. They all go “see how easy it is?!” when they end with a glorious UserForm1.Show without explaining anything about what it means for your code and your understanding of programming concepts, to use a form’s default instance like this. Most don’t even venture into explaining anything about that default instance – and off you go, see you on Stack Overflow.

Because if you don’t know what you’re doing, all you’ve learned is how to write code that, in the name of “hey look it’s so easy”, abstracts away crucially important concepts that will, sooner or later, come back to bite you in the …rear end.

What’s that default instance anyway?

A UserForm is essentially a class module with a designer and a VB_PredeclaredId attribute. That PredeclaredId means VBA is automatically creating a global-scope instance of the class, named after that class. If the default instance is ever unloaded or set to Nothing, its internal state gets reset, and automatically reinitialized as soon as the default instance is invoked again. You can Set UserForm1 = Nothing all you want, you can never verify whether UserForm1 Is Nothing, because that expression will always evaluate to False. A default instance is nice for, say, exposing a factory method. But please, please don’t Show the default instance.


Doing. It. Wrong.™

There are a number of red flags invariably raised in many UserForm tutorials:

  • Unload Me, or worse, Unload UserForm1, in the form’s code-behind. The former makes the form instance a self-destructing object, the latter destroys resets the default instance, and that’s not necessarily the executing instance – and that leads to all kinds of funky unexpected behavior, and embarrassing duplicate questions on Stack Overflow. Every day.
  • UserForm1.Show at the call site, where UserForm1 isn’t a local variable but the “hey look it’s free” default instance, which means you’re using an object without even realizing it (at least without New​-ing it up yourself) – and you’re storing state that belongs to a global instance, which means you’re using an object but without the benefits of object-oriented programming. It also means that…
  • The application logic is implemented in the form’s code-behind. In programming this [anti-]pattern has a name: the “smart UI”. If a dialog does anything beyond displaying and collecting data, it’s doing someone else’s job. That piece of logic is now coupled with the UI, and it’s impossible to write a unit test for it. It also means you can’t possibly reuse that form for something else in the same project (heck, or for something similar in another project) without making considerable changes to the form’s code-behind. A form that’s used in 20 places and runs the show for 20 functionalities, can’t possibly be anything other than a spaghetti mess.

So that’s what not to do. Flipside.


Doing it right.

What you want at the call site is to show an instance of the form, let the user do its thing, and when the dialog closes, the calling code pulls the data from the form’s state. This means you can’t afford a self-destructing form that wipes out its entire state before the [Ok] button’s Click handler even returns.

Hide it, don’t Unload it.

In .NET’s Windows Forms UI framework (WinForms / the .NET successor of MSForms), a form’s Show method is a function that returns a DialogResult enum value, a bit like a MsgBox does. Makes sense; that Show method tells its caller what the user meant to do with the form’s state: Ok being your green light to process it, Cancel meaning the user chose not to proceed – and your program is supposed to act accordingly.

You see Show-ing a dialog isn’t some fire-and-forget business: if the caller is going to be responsible for knowing what to do when the form is okayed or cancelled, then it’s going to need to know whether the form is okayed or cancelled.

And a form can’t tell its caller anything if clicking the [Ok] button nukes the form object.

The basic code-behind for a form with an [Ok] and a [Cancel] button could look like this:

Option Explicit
'@Folder("UI")
Private cancelled As Boolean

Public Property Get IsCancelled() As Boolean
    IsCancelled = cancelled
End Property

Private Sub OkButton_Click()
    Hide
End Sub

Private Sub CancelButton_Click()
    OnCancel
End Sub

Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
    If CloseMode = VbQueryClose.vbFormControlMenu Then
        Cancel = True
        OnCancel
    End If
End Sub

Private Sub OnCancel()
    cancelled = True
    Hide
End Sub

Notice there are two ways to cancel the dialog: the [Cancel] button, and the [X] button, which would also nuke the object instance if Cancel = True wasn’t specified in the QueryClose handler. Handling QueryClose is fundamental – not doing it means even if you’re not Unload-ing it anywhere, [X]-ing out of the form will inevitably cause issues, because the calling code has all rights to not be expecting a self-destructing object – you need to have the form’s object reference around, for the caller to be able to verify if the form was cancelled when .Show returns.

The calling code looks like this:

With New UserForm1
    .Show
    If Not .IsCancelled Then
        '...
    End If
End With

Notice there’s no need to declare a local variable; the With New syntax yields the object reference to the With block, which properly destroys the object whenever the With block is exited – hence why GoTo-jumping out and then back into a With block is never a good idea; this can happen accidentally, with a Resume or Resume Next instruction in an error-handling subroutine.

The Model

A dialog displays and collects data. If the caller needs to know about a UserName and a Password, it doesn’t need to care about some userNameBox and passwordBox textbox controls: what it cares about, is the UserName and the Password that the user provided in these controls – the controls themselves, the ability to hide them, move them, resize them, change their font and border style, etc., is utterly irrelevant. The calling code doesn’t need controls, it needs a model that encapsulates the form’s data.

LoginForm

In its simplest form, the model can take the shape of a few Property Get members in the form’s code-behind:

Public Property Get UserName() As String
    UserName = userNameBox.Text
End Property

Public Property Get Password() As String
    Password = passwordBox.Text
End Property

Or better, it could be a full-fledged class, exposing Property Get and Property Let members for every property.

The calling code can now get the form’s data without needing to care about controls and knowing that the UserName was entered in a TextBox control, or knowing the Password without knowing that the PasswordChar for the passwordBox was set to *.

Except, it can – form controls are basically public instance fields on the form object: the caller can happily access them at will… and this makes the UserName and Password interesting properties kind of lost in a sea of MSForms boilerplate in IntelliSense. So you implement the model in its own class module instead, and use composition to encapsulate it:

Private viewModel As LoginDialogModel

Public Property Get Model() As LoginDialogModel
    Set Model = viewModel
End Property

Public Property Set Model(ByVal value As LoginDialogModel)
    Set viewModel = value
End Property

The model could be updated by the textboxes – it could even expose Boolean properties that can be used to enable/disable the [Ok] button, or show/hide a validation error icon:

Private Sub userNameBox_Change()
    viewModel.UserName = userNameBox.Text
    ValidateForm
End Sub

Private Sub passwordBox_Change()
    viewModel.Password = passwordBox.Text
    ValidateForm
End Sub

Private Sub ValidateForm()
    okButton.Enabled = viewModel.IsValidModel
    userNameValidationErrorIcon.Visible = viewModel.IsInvalidUserName
    passwordValidationErrorIcon.Visible = viewModel.IsInvalidPassword
End Sub

Now, a problem remains: the caller doesn’t want to see the form’s controls.

The View

So we have a model abstraction that the view can consume, but we don’t have an abstraction for the view. That should be simple enough – let’s add a new class module and define a general-purpose IView interface:

Option Explicit
'@Folder("Abstractions")
'@Interface

Public Function ShowDialog(ByVal viewModel As Object) As Boolean
End Function

Now the form can implement that interface – and because the interface is exposing that ShowDialog method, we don’t need a public IsCancelled property anymore. I’m introducing a Private Type at this point, because I like having only one private field:

Option Explicit
Implements IView
'@Folder("UI")

Private Type TView
    IsCancelled As Boolean
    Model As LoginDialogModel
End Type

Private this As TView

Private Sub OkButton_Click()
    Hide
End Sub

Private Sub CancelButton_Click()
    OnCancel
End Sub

Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
    If CloseMode = VbQueryClose.vbFormControlMenu Then
        Cancel = True
        OnCancel
    End If
End Sub

Private Sub OnCancel()
    this.IsCancelled = True
    Hide
End Sub

Private Function IView_ShowDialog(ByVal viewModel As Object) As Boolean
    Set this.Model = viewModel
    Show
    IView_ShowDialog = Not cancelled
End Function

The interface can’t be general-purpose if the Model property is of a type more specific than Object, but it doesn’t matter: the code-behind gets IntelliSense and early-bound, compile-time validation of member calls against it because the Private viewModel field is an implementation detail, and this particular IView implementation is a “login dialog” with a LoginDialogModel; the interface doesn’t need to know, only the implementation.

The [Ok] button will only ever be enabled if the model is valid – that’s one less thing for the caller to worry about, and the logic addressing that concern is neatly encapsulated in the model class itself.

The calling code is supplying the model, so its type is known to the caller – in fact that Property Get member is just provided as a convenience, because it makes little sense to Set a property without being able to Get it later.

Speaking of the calling code, with the addition of a Self property to the model class (Set Self = Me), it could look like this now:

Public Sub Test()
    Dim view As IView
    Set view = New LoginForm

    With New LoginDialogModel
        If Not view.ShowDialog(.Self) Then Exit Sub
        'consume the model:
        Debug.Print .UserName, .Password
    End With 'model goes out of scope

End Sub 'view goes out of scope

If you read the previous article about writing unit-testable code, you’re now realizing (if you haven’t already) that this IView interface could be implemented by some MockLoginDialog class that implements ShowDialog by returning a test-configured value, and unit tests could be written against any code that consumes an IView rather than an actual LoginForm, so long as you’ve written it in such a way that it’s the calling code that’s responsible for knowing what specific IView implementation the code is going to be interacting with.

The model’s validation logic could be unit-tested, too:

Const value As String = "1234"
With New LoginDialogModel
    .Password = value
    Assert.IsTrue .IsInvalidPassword, "'" & value & "' should be invalid."
End With

With a Model and a View, you’re one step away from implementing the New-ing-up a Presenter class, an abstraction that completes the MVP pattern, a much more robust way to write UI-involving code than a Smart UI is.

How to unit test VBA code?

So Rubberduck lets you write unit tests for your VBA code. If you’re learning VBA, or if you’re a seasoned VBA developer but have never written a unit test before, this can sound like a crazy useless idea. I know, because before I started working on Rubberduck, that’s how I was seeing unit tests: annoying, redundant code that tells you nothing F5/debugging doesn’t already tell you.

Right? What’s the point anyway?

First, it changes how you think about code. Things like the Single Responsibility Principle start becoming freakishly important, and you begin to break that monolithic macro procedure into smaller, more focused chunks. Future you, or whoever inherits your code, will be extremely thankful for that.

But not all VBA code should be unit-tested. Let’s see why.

Know what NOT to test

All code has dependencies. Some of these dependencies we can’t really do without, and don’t really affect anything – global-scope functions in the VBA Standard Library, for example. Other dependencies affect global state, require user input (MsgBox, InputBox, forms, dialogs, etc.) or access external resources – like a database, the file system, …or a worksheet.

For the sake of this article, say you have a simple procedure like this:

Public Sub DoSomething()
    Dim conn As ADODB.Connection
    Set conn = New ADODB.Connection
    conn.ConnectionString = "{connection string}"
    conn.Open
    Dim rs As ADODB.Recordset
    Set rs = conn.Execute("SELECT * FROM dbo.SomeTable")
    Sheet1.Range("A1").CopyFromRecordset rs
    conn.Close
End Sub

The problematic dependencies are:

  • conn, an ADODB connection
  • rs, an ADODB recordset
  • Sheet1, an Excel worksheet

Is that procedure doomed and completely untestable? Well, as is, …pretty much: the only way to write a test for this procedure would be to actually run it, and verify that something was dumped into Sheet1. In fact, that’s pretty much automating F5-debug: it’s an integration test, not a unit test – it’s a test, but it’s validating that all components work together. It’s not useless, but that’s not a unit test.

Refactoring

The procedure needs to be parameterless, because it’s invoked from some button: so we have a major problem here – there’s no way to factor out the dependencies!

Or is there? What if we introduced a class, and moved the functionality into there?

Now we’d be looking at this:

Public Sub DoSomething()
    With New MyTestableMacro
        .Run
    End With
End Sub

At this point we tremendously increased the macro’s abstraction level and that’s awesome, but we didn’t really gain anything. Or did we? Now that we’ve decoupled the macro’s entry point from the implementation, we can pull out the dependencies and unit-test the MyTestableMacro class! But how do we do that?

Think in terms of concerns:

  • Pulling data from a database
  • Writing the data to a worksheet

Now think in terms of objects:

  • We need some data service responsible for pulling data from a database
  • We need some spreadsheet service responsible for writing data to a worksheet

The macro might look like this now:

Public Sub DoSomething()

    Dim dataService As MyDbDataService
    Set dataService = New MyDbDataService

    Dim spreadsheetService As Sheet1Service
    Set spreadsheetService = New Sheet1Service

    With New MyTestableMacro
        .Run dataService, spreadsheetService
    End With

End Sub

Now if we think of MyDbDataService as an interface, we could conceptualize it like this:

Option Explicit
'@Folder "Services.Abstract"
'@Interface IDataService

Public Function GetSomeTable() As Variant
End Function

And if we think of Sheet1Service as an interface, we could conceptualize it like this:

Option Explicit
'@Folder "Services.Abstract"
'@Interface IWorksheetService

Public Sub WriteAllData(ByRef data As Variant)
End Sub

Notice the interfaces don’t know or care about ADODB.Recordset: the last thing we want is to have that dependency in our way, so we’ll be passing a Variant array around instead of a recordset.

Now the Run method’s signature might look like this:

Public Sub Run(ByVal dataService As IDataService, ByVal wsService As IWorksheetService)

Notice it only knows about abstractions, not the concrete implementations. All that’s missing is to make MyDbDataService implement the IDataService interface, and Sheet1Service implement the IWorksheetService interface.

Option Explicit
Implements IDataService
'@Folder "Services.Concrete"

Private Function IDataService_GetSomeTable() As Variant
    Dim conn As ADODB.Connection
    Set conn = New ADODB.Connection
    conn.ConnectionString = "{connection string}"
    conn.Open
    Dim rs As ADODB.Recordset
    Set rs = conn.Execute("SELECT * FROM dbo.SomeTable")
    'dump the recordset onto a temp sheet:
    Dim tempSheet As Excel.Worksheet
    Set tempSheet = ThisWorkbook.Worksheets.Add
    tempSheet.Range("A1").CopyFromRecordset rs
    IDataService_GetSomeTable = tempSheet.UsedRange.Value '2D variant array
    conn.Close
    tempSheet.Delete
End Function

Stubbing the interfaces

So here’s where the magic begins: the macro will definitely be using the above implementation, but nothing forces a unit test to use it too. A unit test would be happy to use something like this:

Option Explicit
Implements IDataService
'@Folder "Services.Stubs"

Private Function IDataService_GetSomeTable() As Variant
    Dim result(1 To 50, 1 To 10) As Variant
    IDataService_GetSomeTable = result
End Function

Public Function GetSomeTable() As Variant
    GetSomeTable = IDataService_GetSomeTable
End Function

You could populate the array with some fake results, expose properties and methods to configure the stub in every way your tests require (depending on what logic needs to run against the data after it’s dumped onto the worksheet) – for this example though all we need is for the method to return a 2D variant array, and the above code satisfies that.

Then we need a stub for the IWorksheetService interface, too:

Option Explicit
Implements IWorksheetService
'@Folder "Services.Stubs"

Private written As Boolean
Private arrayPointer As Long

Private Sub IWorksheetService_WriteAllData(ByRef data As Variant)
    written = True
    arrayPointer = VarPtr(data)
End Function

Public Property Get DataWasWritten() As Boolean
    DataWasWritten = written
End Property

Public Property Get WrittenArrayPointer() As Long
    WrittenArrayPointer = arrayPointer
End Property

Writing the tests

That’s all our test needs for now. See where this is going? DoSomething is using concrete implementations of the service interfaces that actually do the work, and a unit test can look like this:

'@TestMethod
Public Sub GivenData_WritesToWorksheet()
    'Arrange
    Dim dataServiceStub As MyDataServiceStub
    Set dataServiceStub = New MyDataServiceStub
    Dim wsServiceStub As MyWorksheetServiceStub
    Set wsServiceStub = New MyWorksheetServiceStub

    'Act
    With New MyTestableMacro
        .Run dataServiceStub, wsServiceStub
    End With

    'Assert
    Assert.IsTrue wsServiceStub.DataWasWritten
End Sub

If MyTestableMacro.Run invokes IWorksheetService.WriteAllData, this test will pass.

One more:

'@TestMethod
Public Sub WorksheetServiceWorksOffDataFromDataService()
    'Arrange
    Dim dataServiceStub As MyDataServiceStub
    Set dataServiceStub = New MyDataServiceStub
    Dim expected As Long
    expected = VarPtr(dataServiceStub.GetSomeTable)

    Dim wsServiceStub As MyWorksheetServiceStub
    Set wsServiceStub = New MyWorksheetServiceStub

    'Act
    With New MyTestableMacro
        .Run dataServiceStub, wsServiceStub
    End With

    Dim actual As Long
    actual = wsServiceStub.WrittenArrayPointer

    'Assert
    Assert.AreEqual expected, actual
End Sub

If the worksheet service receives the exact same array that the data service returned, this test should pass.

That was a relatively trivial example – the overhead (5 classes, including 2 interfaces and 2 stub implementations) is probably not justified given the simplicity of the task at hand (pull data from a database, dump that data to a worksheet). But hopefully it illustrates a number of things:

  • How to pull dependencies out of the logic that needs to be tested.
  • How to abstract the dependencies as interfaces.
  • How to implement test stubs for these dependencies, and how stubs can expose members that aren’t on the interface, for the tests to consume.
  • How unit tests document what the code is supposed to be doing, through descriptive naming.
  • VBA code can be just as object-oriented as any other code, with full-blown polymorphism and dependency injection.

Next tutorial should be about MSForms.UserForm, how not to use it, and how to test code that needs to pop a dialog. I didn’t mention anything about Rubberduck’s Fakes framework here either, but know that if one of your dependencies is a MsgBox and you have different code paths depending on whether the user clicked [Ok] or [Cancel], you can use Rubberduck’s Fakes API to literally configure how the MsgBox statement is going to behave when it’s invoked by a Rubberduck test.

Rubberduck 2.1.x

The release was going to include a number of important fixes for the missing annotation/attribute inspection and quick-fix, but instead we disabled it, along with a few other buggy inspections, and pushed the release – 7 months after 2.0.13, the last release was now over 1,300 commits behind, and we were reaching a point where we knew a “green release” was imminent, but also a point where we were going to have to make some more changes to parts of the core – notably in order to implement the fixes for these broken annotation/attribute inspections.

So we shipped what we had, because we wouldn’t jeopardize the 2.1 release with parser logic changes at that point.

Crossroads

wooden_signpost_at_the_crossroads1
By Hillebrand Steve, U.S. Fish and Wildlife Service [Public domain], via Wikimedia Commons
So here we are, at the crossroads: with v2.1.0 released, things are going to snowball – there’s a lot on our plates, but we now have a solid base to build upon. Here’s what’s coming:

  • Castle Windsor IoC: hopefully-zero user-facing changes, we’re replacing good old Ninject with a new dependency injection framework in order to gain finer control over object destruction – we will end up correctly unloading!

That’s actually priority one: the port is currently under review on GitHub, and pays a fair amount of long-standing technical debt, especially with everything involving menus.

  • Annotation/Attributes: fixing these inspection, and the quick-fix that synchronizes annotations with module attributes and vice-versa, will finally expose VB module and member attributes to VBA code panes, using Rubberduck’s annotation syntax.

For example,  adding '@Description("This procedure does XYZ") on top of a procedure will tell Rubberduck that you mean that procedure to have a VB_Description attribute; when Rubberduck parses that module after you synchronize, it will be able to use that description in the context status bar, or as tooltips in the Code Explorer.

This is considered a serious issue, because it affects pretty much every single inspection. Luckily there’s a [rather annoying and not exactly acceptable] work-around (apply the fix bottom-to-top in a module), but still.

But there’s a Greater Picture, too.

The 2.1.x Cycle

At the end of this development cycle, Rubberduck will:

  • Work in the VB6 IDE;
  • Have formalized the notion of an experimental feature;
  • Have a working Extract Method refactoring;
  • Make you never want to use the VBE’s Project References dialog ever again;
  • Compute and report various code metrics, including cyclomatic complexity and nesting levels, and others (and yes, line count too);
  • Maybe analyze a number of execution paths and implement some of the coolest code inspections we could think of;
  • Be ready to get really, really serious about a tear-tab AvalonEdit code pane.

If all you’re seeing is Rubberduck’s version check, the next version you’ll be notified about will be 2.1.2, for which we’re shooting for 2017-11-13. If you want to try every build until then (or just a few), then you’ll want to keep an eye on our releases page!