Dependency Injection + Inversion of Control + VBA

Whether VBA can do serious OOP isn’t a question – it absolutely can: none of the SOLID principles have implications that disqualify VBA as a language, and this means we can implement dependency injection and inversion of control. This article will go over the general principles, and then subsequent articles will dive into various dependency injection techniques you can use in VBA code.

A quick summary of these fundamental guidelines, before we peek at DI and IoC:

SOLID

Single Responsibility Principle

Split things up, and then some. Write loop bodies in another procedure, extract if/else blocks into other small specialized procedures. Do as little as possible, aim for each procedure to have a well-defined single responsibility.

Open/Closed Principle

Designing classes that are “open for extension, but closed for modification” is much easier said than done, but definitely worth striving for; by adhering to the other SOLID principles, this one just naturally falls into place. In a nutshell, you’ll want to be able to add features by extending a class rather than modifying it (and risk breaking something) – the only code you need to think about is the code for the new feature… and how you’re going to be testing it.

Liskov Substitution Principle

Say you write a procedure that takes an IFooRepository parameter. Whether you invoke it with some SqlFooRepository, MySqlFooRepository, or FakeFooRepository, should make no difference whatsoever: each implementation fulfills the interface’s contract, each implementation could be swapped for another without altering the logic of the procedure.

Interface Segregation Principle

Write small, specialized interface with a clear purpose, that won’t likely need to grow new members in the future: IFooRepository.GetById is probably fine, but IFooRepository.GetByName looks like someone had a specific or particular implementation in mind when they designed the interface, and now you need to implement a GetByName method for a repository where that makes no sense.

Dependency Inversion Principle

Depend on abstractions, not concrete implementations – your code has dependencies, and you want them abstracted away behind interfaces that you receive as parameters.


What is a dependency?

You’re writing a procedure, and you need to invoke a method that belongs to another object or module – say, MsgBox: with it your procedure can warn the user of an error, or easily get a yes/no answer. But this ability comes with a cost: now there’s no way to invoke that procedure without popping a message box and stopping execution until it’s dismissed. Hard-wired dependencies make unit testing difficult (if not impossible), so we inject them instead, as abstractions.

And dependency injection?

MsgBox is a bad example – Rubberduck’s FakesProvider already lets you configure MsgBox calls any way your testing requires, and no pop-up ..pops up. But let’s say the procedure needs to do things to a Worksheet.

We could make the procedure take a Worksheet parameter, and that would be method injection.

Since we’re in a class module (right?), we could have a Property Set member that takes a Worksheet value argument and assigns it to a Worksheet instance field that our method can work with, and that would be property injection.

We could have a factory method on our class’ default instance, that receives a Worksheet argument and property-injects it to a New instance of the class, then returns an instance of the class that’s ready to use (behind an interface that doesn’t expose any Property Set accessor for the injected dependencies), and that would be as close to the ideal constructor injection as you could get in a language without constructors.

What “control” is inverted, and why?

When a method News up all its dependencies, it’s a control freak that doesn’t let the outside world know anything about what objects it needs to do its job: it’s a black box that other code needs to take as “it just works”, and we can’t do much to alter how it works.

With inversion of control (IoC), you give up that control and let something else New things up for you, and that’s why Dependency Injection (DI) goes hand-in-hand with it. IoC implies completely reversing the dependency graph. Take a UserForm that reads from / writes to a worksheet, with code-behind that implements every little bit of what needs to happen in CommandButton1_Click handlers – a “Smart UI” – reversing the dependency graph means the form’s code-behind is now only concerned about the data it needs to present to the user, and the data it needs to collect from the user; the CommandButton1 button was renamed to AcceptButton, and its Click handler does one single thing: it invokes a SaveChangesCommand object’s Execute method, and everything that was in that click handler is now in that ICommand implementation. The command knows nothing of any userform; it works with the model, that it receives in an Object parameter to its Execute method.

It all comes down to one thing: testability. You want to test your commands and what they do, how they manipulate the model – so you pull as much as possible out of UI-dependent code and into specialized classes that only know as much as they need to know. The form’s code-behind (aka the view) knows about the model, the commands; the model knows about nothing but itself; the commands know about the model; a presenter would know about both the view and the model, but shouldn’t need to care for commands.

If none of the components create their dependencies / if all components have their dependencies injected, then if we follow the dependency chain we arrive to an entry point: in VB6 that would be some Public Sub Main(); in VBA, that could be any Public Sub procedure / “macro” in a standard module, or any Worksheet or Workbook event handler. These entry points all need to New up (or otherwise provide) everything in the dependency graph (e.g. class1 depends on class2 which depends on class3 and class4, …), and then invoke the desired functionality.

What is testable code?

Testable code is code for which you can fully control/inject all the dependencies of that code. This is where coding against abstractions pays off: you can leverage polymorphism and implement test doubles / stubs / fakes as needed. The presence of a New keyword in a method is a rather obvious indicator of a dependency; it’s the implicit dependencies that are harder to spot. These could be a MsgBox prompt, a UserForm dialog, but also Open, Close, Write, Kill, Name keywords, or maybe ActiveSheet, or ActiveWorkbook implicit member calls against a hidden global object; even the current Date can be a hidden dependency if it’s involved in behavior you want to cover with one or more unit tests. The Rnd function is definitely a dependency as well.

SOLID code is inherently testable code. If you write the tests first (Test-Driven Development / TDD), you could even conceivably end up with SOLID-compliant code out of necessity.

Say you want to bring up a dialog that collects some inputs, and one of these inputs needs to be a decimal value greater than or equal to 0 but less than 1 – what are the odds that such validation logic ends up buried in some TextBox12_Change handler (and duplicated in 3 places) in the UserForm module if the problem is tackled from a testability standpoint? That’s right: exactly none.

If the first thing you do is create a MyViewModelTests module with a MySpecialDecimal_InvalidIfGreaterThanOne test method, there’s a good chance your next move could be to add a MyViewModel class with a MySpecialDecimal property – be it only so that the test method can compile:

'@TestMethod("ValidationTests")
Public Sub MySpecialDecimal_InvalidIfGreaterThanOne()
    Dim sut As MyViewModel
    Set sut = New MyViewModel
    sut.MySpecialDecimal = 42
    Assert.IsFalse sut.IsValid
End Sub

So we need this MyViewModel.IsValid member now:

Public Property Get IsValid() As Boolean
End Property

At this point we can run the test in Rubberduck’s Test Explorer, and see it fail. Never trust a test you’ve never seen fail! The next step is to write just enough code to make the test pass:

Public Property Get IsValid() As Boolean
    IsValid = MySpecialDecimal < 1
End Property

This prompts us to write another test that we know would fail:

'@TestMethod("ValidationTests")
Public Sub MySpecialDecimal_InvalidIfNegative()
    Dim sut As MyViewModel
    Set sut = New MyViewModel
    sut.MySpecialDecimal = -1
    Assert.IsFalse sut.IsValid
End Sub

So we tweak the code to make it pass:

Public Property Get IsValid() As Boolean
    IsValid = MySpecialDecimal >= 0 And MySpecialDecimal < 1
End Property

We then run the whole test suite, to validate that this change didn’t break any green test, which would mean a regression bug was introduced – and the red test is telling you exactly which input scenario broke.


In a vanilla VBE, OOP quickly gets out of hand, for any decently-sized project: wading through many class modules in the legacy editor, locating implementations of the interfaces you’re coding against – things that you would seamlessly deal with in a modern IDE, become excruciatingly painful when modules are all listed alphabetically under one single “classes” folder, and when Ctrl+F “Implements {name}” is the only thing that can help you locate interface implementations.

Rubberduck not only addresses the organization of your OOP project (with “@Folder” annotations that let you organize & regroup modules by functionality) and enhances navigation tooling (“find all implementations”, “find all references”, “find symbol”, etc.), it also provides a unit testing framework, so that testing your VBA code is done the same way it’s done in other languages and modern IDEs, with Assert expressions that make or break a green test.

But if you write unit tests for your object-oriented VBA code, you’ll quickly notice that when your tests need to inject a fake implementation of a dependency, a consequence is that you often end up with a lot of “test fake” classes whose sole purpose is to support unit testing. This is double-edged, because you need to be careful that you’re testing the right thing (i.e. the actual object/method under test) and not whether your test fake/stub is behaving correctly.

Rubberduck has well over 5K unit tests, and most of them would be very hard to implement without the ability to setup proper mocking. Using the popular Moq framework, we are able to create and configure these “test fakes” without actually writing a class that implements the interface we need to inject into the component we’re testing.

Soon, these capabilities will land in the VBA landscape, with Rubberduck’s unit testing tools wrapping up Moq to let VBA code do exactly that.

Code Insights with Rubberduck + Excel

You’re writing a rather large VBA/VB6 project, and you’re starting to have a sizable amount of passing unit tests. Did you know you can copy the test results to the clipboard with a single click?

…and then paste them onto a new worksheet and turn it into a data table:

If you’re not sure what to do next, you can even let Excel give you ideas – you’ll find the Recommended Charts button under the Insert Ribbon tab:

With the count of method by component chart, we can see what test modules have more test methods; the sum of duration by component chart can show us which test modules take the longer to execute – or we could average it across test categories, or archive test results and later aggregate them… and then use this data to performance-profile problematic test scenarios.

Similarly, the “Copy to Clipboard” button from the Code Explorer can be used to export a table into Excel, and using the recommended pivot tables feature, we can get a detailed breakdown of the project – for example count of names by declaration type creates a pivot table that lists all Rubberduck declaration types, so you can easily know how many line labels your project has, or how many Declare Function imports are used:

With a little bit of filtering and creativity, we can regroup all Constant, Function, PropertyGet and Variable declarations by return type, and easily identify, say, everything that returns a Variant:

The possibilities are practically endless: the data could be timestamped and exported to some Access or SQL Server database, to feed some dashboard or report showing how a project grows over time.

How would you analyze your VBA projects? What code metrics would you like to be able to review and pivot like this? Share your ideas, or implement them, and send a pull request our way!

OOP Battleship Part 3: The View

Download the macro-enabled Excel workbook here

Now that we have defined our model, we need a view. In MVC terms, the view is the component that’s making the game state visible to the player; it is responsible for the two-way communication with the controller. Since we’re in Microsoft Excel, we can use a worksheet to do this. So we craft a lovely-looking Battleship game screen:

pgyam

I used a stock image for the background, spent more time than I probably should have looking for images of the game ships, and used a number of rounded rectangle shapes to make various boxes and buttons – the clickable ones being attached to sheet-local macros. The two game grids use a customized 5-icon conditional format that not-so-coincidentally map to the GridState enum values:

jxpfw

If you recall from the previous post, the GridState enum was defined as follows:

Public Enum GridState
'@Description("Content at this coordinate is unknown.")
Unknown = -1
'@Description("Unconfirmed friendly ship position.")
PreviewShipPosition = 0
'@Description("Confirmed friendly ship position.")
ShipPosition = 1
'@Description("Unconfirmed invalid/overlapping ship position.")
InvalidPosition = 2
'@Description("No ship at this coordinate.")
PreviousMiss = 3
'@Description("An enemy ship occupies this coordinate.")
PreviousHit = 4
End Enum

The PlayerGrid class has a StateArray read-only property that returns a 2D variant array with Unknown values being Empty, and the rest of the state values being returned as-is: this means in order to “refresh” the view, all we need to do is dump this 2D variant array onto the appropriate game grid, and we’re done!

Private Property Get PlayerGrid(ByVal gridId As Byte) As Range
    Set PlayerGrid = Me.Names("PlayerGrid" & gridId).RefersToRange
End Property

Public Sub RefreshGrid(ByVal grid As PlayerGrid)
    Application.ScreenUpdating = False
    Me.Unprotect
    PlayerGrid(grid.gridId).Value = Application.WorksheetFunction.Transpose(grid.StateArray)
    Me.Protect
    Me.EnableSelection = xlUnlockedCells
    Application.ScreenUpdating = True
End Sub

Listing all the code here like I did for the model post would be rather boring, so I’m not going to do that. If the model was just a handful of classes with factory methods and explicit interfaces, the view is much more interesting as a concept.

The worksheet handles 3 worksheet events:

Private Sub Worksheet_BeforeDoubleClick(ByVal target As Range, ByRef Cancel As Boolean)
    Cancel = True
    Dim gridId As Byte
    Dim position As IGridCoord
    Set position = RangeToGridCoord(target, gridId)
    If Mode = FleetPosition Or Mode = player1 And gridId = 2 Or Mode = player2 And gridId = 1 Then
        RaiseEvent DoubleClick(gridId, position, Mode)
    End If
End Sub

Private Sub Worksheet_BeforeRightClick(ByVal target As Range, Cancel As Boolean)
    Cancel = True
    If Mode = FleetPosition Then
        Dim gridId As Byte
        Dim position As IGridCoord
        Set position = RangeToGridCoord(target, gridId)
        RaiseEvent RightClick(gridId, position, Mode)
    End If
End Sub

Private Sub Worksheet_SelectionChange(ByVal target As Range)
    Dim gridId As Byte
    Dim position As IGridCoord
    Set position = RangeToGridCoord(target, gridId)
    If Not position Is Nothing Then
        Me.Unprotect
        CurrentSelectionGrid(gridId).Value = position.ToA1String
        CurrentSelectionGrid(IIf(gridId = 1, 2, 1)).Value = Empty
        Me.Protect
        Me.EnableSelection = xlUnlockedCells
        RaiseEvent SelectionChange(gridId, position, Mode)
    End If
End Sub

Notice these aren’t doing anything really – they merely work out a way to talk to another component – see, making a worksheet (or any document module class) implement an interface is a very bad idea: don’t do it (unless you like to crash the host and lose everything). So instead, we make another class implement the “view” interfaces, and make that class talk to the worksheet – a bit like we did in There is no worksheet.

The view needs two interfaces: one for the controller to send messages to the view, and the other for the view to send messages to the controller. If we call controller-to-view messages “commands”, and view-to-controller messages “events”, then the names IGridViewEvents and IGridViewCommands make complete sense!

So the WorksheetView class (not the GameSheet worksheet) implements the IGridViewCommands interface, like this:

Private Sub IGridViewCommands_OnBeginAttack(ByVal currentPlayerGridId As Byte)
    sheetUI.ShowInfoBeginAttackPhase currentPlayerGridId
End Sub

Private Sub IGridViewCommands_OnBeginShipPosition(ByVal currentShip As IShip, ByVal player As IPlayer)
    sheetUI.ShowInfoBeginDeployShip currentShip.Name
End Sub

Private Sub IGridViewCommands_OnBeginWaitForComputerPlayer()
    Application.Cursor = xlWait
    Application.StatusBar = "Please wait..."
End Sub

the WorksheetView class also handles the custom events sent from the worksheet, like this:

Private Sub sheetUI_DoubleClick(ByVal gridId As Byte, ByVal position As IGridCoord, ByVal Mode As ViewMode)
    Select Case Mode
        
        Case ViewMode.FleetPosition
            ViewEvents.ConfirmShipPosition gridId, position
            
        Case ViewMode.player1, ViewMode.player2
            ViewEvents.AttackPosition gridId, position
            
    End Select
End Sub

Private Sub sheetUI_PlayerReady()
    ViewEvents.HumanPlayerReady
End Sub

Private Sub sheetUI_RightClick(ByVal gridId As Byte, ByVal position As IGridCoord, ByVal Mode As ViewMode)
    If Mode = FleetPosition Then ViewEvents.PreviewRotateShip gridId, position
End Sub

Private Sub sheetUI_SelectionChange(ByVal gridId As Byte, ByVal position As IGridCoord, ByVal Mode As ViewMode)
    If Mode = FleetPosition Then ViewEvents.PreviewShipPosition gridId, position
End Sub

So what is this ViewEvents? If VBA allowed an interface to expose events, we wouldn’t need it: we would simply raise an event to relay the message directly to the controller, who would then handle the view events and respond with a command back to the view. But VBA does not let us expose events on an interface, so this is where the adapter pattern kicks in.

We have a GridViewAdapter class that implements both IGridViewEvents and IGridViewCommands interfaces; the WorksheetView holds a (weak) reference to the adapter, through its IGridViewEvents interface – so ViewEvents.AttackPosition is a method on the adapter.

The GridViewAdapter class receives these messages from the view, and relays them back to the controller, via events:

Private Sub IGridViewEvents_AttackPosition(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnAttackPosition(gridId, position)
End Sub

Private Sub IGridViewEvents_ConfirmShipPosition(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnConfirmCurrentShipPosition(gridId, position)
End Sub

Private Sub IGridViewEvents_CreatePlayer(ByVal gridId As Byte, ByVal pt As PlayerType, ByVal difficulty As AIDifficulty)
    RaiseEvent OnCreatePlayer(gridId, pt, difficulty)
End Sub

Private Sub IGridViewEvents_HumanPlayerReady()
    RaiseEvent OnPlayerReady
End Sub

Private Sub IGridViewEvents_PreviewRotateShip(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnRotateCurrentShipPosition(gridId, position)
End Sub

Private Sub IGridViewEvents_PreviewShipPosition(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnPreviewCurrentShipPosition(gridId, position)
End Sub

The GameController has a Private WithEvents viewAdapter As GridViewAdapter private field, and with that it’s able to respond to the adapter’s events and, say, create a HumanPlayer in grid 1, or a MercilessAI AI player in grid2 – and then instruct the view to begin positioning the ships, one by one, until the game is ready to begin.

Apart from events, the worksheet exposes methods that display, hide, or flash such or such shape, depending on what the controller says needs to happen next: the worksheet doesn’t control anything whatsoever about the game mechanics – that’s the controller’s job. The view raises events, the adapter handles them and relays them to the controller; controller alters game state, and then sends a command to the view to reflect the current state.

This makes the controller blissfully unaware about any worksheet, or event about any WorksheetView class: it knows about the GridViewAdapter, but then looking at how the game is started…

Public Sub PlayWorksheetInterface()
    Dim view As WorksheetView
    Set view = New WorksheetView
    
    Dim randomizer As IRandomizer
    Set randomizer = New GameRandomizer
    
    Set controller = New GameController
    controller.NewGame GridViewAdapter.Create(view), randomizer
End Sub

…we can easily infer that the adapter would work with any class that implements the IGridViewCommands interface and that’s able to “adapt” its event model to the IGridViewEvents methods: the components are said to be decoupled; we can easily swap one implementation for another – be it for unit-testing the individual components… or we could implement a view that has nothing to do with any Excel worksheet.

We could easily add another button to the start screen, attach it to some PlayUserFormInterface macro, and do something like this:

Public Sub PlayUserFormInterface()
    Dim view As UserFormView
    Set view = New UserFormView
    
    Dim randomizer As IRandomizer
    Set randomizer = New GameRandomizer
    
    Set controller = New GameController
    controller.NewGame GridViewAdapter.Create(view), randomizer
End Sub

And then play the exact same game with a UI that’s entirely different.

OOP Battleship Part 2: The Model

Download the macro-enabled Excel workbook here

Merciless.png
“Merciless” AI (Player1) this close to winning this game

So we’re making a game of Battleship, and we’re going to do this using an object-oriented pattern called Model-View-Controller (MVC). The first thing we need to do, is to modelize the problem in terms of objects. We’re going to need:

  • Player object, so that we know who’s playing on which grid. A player might be human or computer-controlled, and a player has a grid.
  • PlayerGrid object, so that we know the state of each player’s game grid; a player’s grid has a number of ships on it.
  • Ship object that we can place on a player’s grid. A ship has a size and an orientation – we can place them anywhere on the grid, horizontally or vertically; a ship is also going to need to know where it’s hit and whether it’s sunken.
  • GridCoordinate object, to encapsulate X and Y positions and make it easy to pass these two values together as a single entity. This object could have an Offset method that gives us another coordinate at a relative X or Y position.

These objects solve the problem space of modelizing a game of Battleship: with them we have everything we need to track game state. We’ll need something else that can make the players take turns at shooting missiles at each other’s grid, but that will be the controller‘s job; we’ll also need something else that can display the game state and take a human user’s inputs, but that will be the view‘s job. The role of the model is to encapsulate the data that we need to manipulate, and with these objects we’ve got everything we need… for now.

GridCoordinate

Let’s start with the grid coordinates system, since that is our smallest building block, and a grid coordinate doesn’t need to know about a ship or a player interface. We want a grid coordinate to be read-only: once an instance is created for position A1, it’s A1 and remains A1. We want to be able to determine if two grid coordinates are the same without needing to check for both X and Y coordinates every time, and a function that returns True when a coordinate is adjacent to another would be useful, too. Next we’ll want a string representation of the coordinate that lines up with the A1 notation of the game grid, but it would also be useful to have a (x,y) representation that can easily round-trip from a string to a grid coordinate and back, without needing to work out the column number for H.

So the IGridCoord interface would look like this:

'@Folder("Battleship.Model")
'@Description("Describes a coordinate in a 2D grid.")
'@Interface
Option Explicit

'@Description("Gets the horizontal position.")
Public Property Get X() As Long
End Property

'@Description("Gets the vertical position.")
Public Property Get Y() As Long
End Property

'@Description("Creates and returns a new coordinate by offsetting this instance.")
Public Function Offset(Optional ByVal xOffset As Long, Optional ByVal yOffset As Long) As IGridCoord
End Function

'Description("Returns True if the specified coordinate is adjacent to this instance.")
Public Function IsAdjacent(ByVal other As IGridCoord) As Boolean
End Function

'@Description("Returns True if the specified coordinate describes the same location as this instance.")
Public Function Equals(ByVal other As IGridCoord) As Boolean
End Function

'@Description("Returns a (x,y) string representation of this instance.")
Public Function ToString() As String
End Function

'@Description("Returns a A1 string representation of this instance.
Public Function ToA1String() As String
End Function

We’re making it an interface, because otherwise there would be no way of exposing X and Y properties as read-only values. Now we’re going to be writing the game against this IGridCoord interface, rather than against the GridCoord class directly. In order to make it easy to create a grid coordinate by providing an X and an Y value, we’ll give the class a predeclared ID, and use its default instance not to store state, but to expose convenient factory methods.

The listing includes module attributes, so don’t juse copy-paste this in the VBE: you need to import it in a VBA project for it to work.

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "GridCoord"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = True
'@Folder("Battleship.Model")
'@IgnoreModule UseMeaningfulName; X and Y are perfectly fine names here.
Option Explicit
Implements IGridCoord

Private Type TGridCoord
    X As Long
    Y As Long
End Type

Private this As TGridCoord

Public Function Create(ByVal xPosition As Long, ByVal yPosition As Long) As IGridCoord
    With New GridCoord
        .X = xPosition
        .Y = yPosition
        Set Create = .Self
    End With
End Function

Public Function FromString(ByVal coord As String) As IGridCoord
    coord = Replace(Replace(coord, "(", vbNullString), ")", vbNullString)

    Dim coords As Variant
    coords = Split(coord, ",")

    If UBound(coords) - LBound(coords) + 1  2 Then Err.Raise 5, TypeName(Me), "Invalid format string"

    Dim xPosition As Long
    xPosition = coords(LBound(coords))

    Dim yPosition As Long
    yPosition = coords(UBound(coords))

    Set FromString = Create(xPosition, yPosition)
End Function

Public Property Get Self() As IGridCoord
    Set Self = Me
End Property

Public Property Get X() As Long
    X = this.X
End Property

Public Property Let X(ByVal value As Long)
    this.X = value
End Property

Public Property Get Y() As Long
    Y = this.Y
End Property

Public Property Let Y(ByVal value As Long)
    this.Y = value
End Property

Public Property Get Default() As IGridCoord
    Set Default = New GridCoord
End Property

Public Function ToString() As String
    ToString = "(" & this.X & "," & this.Y & ")"
End Function

Private Function IGridCoord_Equals(ByVal other As IGridCoord) As Boolean
    IGridCoord_Equals = other.X = this.X And other.Y = this.Y
End Function

Private Function IGridCoord_IsAdjacent(ByVal other As IGridCoord) As Boolean
    If other.Y = this.Y Then
        IGridCoord_IsAdjacent = other.X = this.X - 1 Or other.X = this.X + 1
    ElseIf other.X = this.X Then
        IGridCoord_IsAdjacent = other.Y = this.Y - 1 Or other.Y = this.Y + 1
    End If
End Function

Private Function IGridCoord_Offset(Optional ByVal xOffset As Long, Optional ByVal yOffset As Long) As IGridCoord
    Set IGridCoord_Offset = Create(this.X + xOffset, this.Y + yOffset)
End Function

Private Function IGridCoord_ToString() As String
    IGridCoord_ToString = Me.ToString
End Function

Private Function IGridCoord_ToA1String() As String
    IGridCoord_ToA1String = Chr$(64 + this.X) & this.Y
End Function

Private Property Get IGridCoord_X() As Long
    IGridCoord_X = this.X
End Property

Private Property Get IGridCoord_Y() As Long
    IGridCoord_Y = this.Y
End Property

So from the default instance, we have access to Create and FromString factory methods, a convenient Default property that gives a (0,0) default coordinate that should be equivalent to the class’ default instance; the writable X and Y properties are meant for instance state: they make no sense outside a factory method.

And now we can create and use a grid coordinate like this:

Dim position As IGridCoord
Set position = GridCoord.Create(3, 4)
Debug.Print position.ToA1String

We can also write a suite of test methods that validate that our GridCoord class behaves as expected in every case… and then make a PlayerGrid class, to represent each player’s grid.

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "PlayerGrid"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = True
'@Folder("Battleship.Model.Player")
Option Explicit

Private Const GridSize As Byte = 10
Private Const MaxShipsPerGrid As Byte = 5

Private Const KnownGridStateErrorMsg As String _
    = "Specified coordinate is not in an unknown state."
Private Const CannotAddShipAtPositionMsg As String _
    = "Cannot add a ship of this size at this position."
Private Const CannotAddMoreShipsMsg As String _
    = "Cannot add more ships to this grid."

Public Enum PlayerGridErrors
    KnownGridStateError = vbObjectError Or 127
    CannotAddShipAtPosition
    CannotAddMoreShips
End Enum

Public Enum AttackResult
    Miss
    Hit
    Sunk
End Enum

Public Enum GridState
    '@Description("Content at this coordinate is unknown.")
    Unknown = -1
    '@Description("Unconfirmed friendly ship position.")
    PreviewShipPosition = 0
    '@Description("Confirmed friendly ship position.")
    ShipPosition = 1
    '@Description("Unconfirmed invalid/overlapping ship position.")
    InvalidPosition = 2
    '@Description("No ship at this coordinate.")
    PreviousMiss = 3
    '@Description("An enemy ship occupies this coordinate.")
    PreviousHit = 4
End Enum

Private Type TPlayGrid
    Id As Byte
    ships As Collection
    State(1 To GridSize, 1 To GridSize) As GridState
End Type

Private this As TPlayGrid

Public Function Create(ByVal gridId As Byte) As PlayerGrid
    With New PlayerGrid
        .gridId = gridId
        Set Create = .Self
    End With
End Function

Public Property Get Self() As PlayerGrid
    Set Self = Me
End Property

Of course there’s more to it, but just listing it here would get boring – the important part is that there’s a GridState array, and a collection of ships. And then these GridState and AttackResult enums.

One important method is TryHit, which is the mechanism that sets the internal state to PreviousHit or PreviousMiss, depending on whether there’s a ship at the specified position – and if there’s one, we return a ByRef reference to it, so that the controller can tell the view to update that ship’s status:

'@Description("(side-effecting) Attempts a hit at the specified position; returns the result of the attack, and a reference to the hit ship if successful.")
Public Function TryHit(ByVal position As IGridCoord, Optional ByRef hitShip As IShip) As AttackResult
    
    If this.State(position.X, position.Y) = GridState.PreviousHit Or _
       this.State(position.X, position.Y) = GridState.PreviousMiss Then
        Err.Raise PlayerGridErrors.KnownGridStateError, TypeName(Me), KnownGridStateErrorMsg
    End If
    
    Dim currentShip As IShip
    For Each currentShip In this.ships
        If currentShip.Hit(position) Then
            this.State(position.X, position.Y) = GridState.PreviousHit
            If currentShip.IsSunken Then
                TryHit = Sunk
            Else
                TryHit = Hit
            End If
            Set hitShip = currentShip
            Exit Function
        End If
    Next
    
    this.State(position.X, position.Y) = GridState.PreviousMiss
    TryHit = Miss
    
End Function

Another important function is FindHitArea, which the AI player uses when it wants to hunt down a damaged ship – it returns a collection of collections of previously hit grid positions, that the AI player can then analyze to try and infer a direction:

'@Description("Finds area around a damaged ship, if one exists.")
Public Function FindHitArea() As Collection
    Dim currentShip As IShip
    For Each currentShip In this.ships
        If Not currentShip.IsSunken Then
            Dim currentAreas As Collection
            Set currentAreas = currentShip.HitAreas
            If currentAreas.Count > 0 Then
                Set FindHitArea = currentAreas(1)
                Exit Function
            End If
        End If
    Next
End Function

Lastly, the Scamble method is invoked for AI players’ grid – it replaces confirmed ship positions with unknown states, so that the AI enemy ships are hidden. Without this method, the AI-positioned ships would be in plain sight!

'@Description("Removes confirmed ship positions from grid state.")
Public Sub Scramble()
    Dim currentX As Long
    For currentX = 1 To GridSize
        Dim currentY As Long
        For currentY = 1 To GridSize
            If this.State(currentX, currentY) = GridState.ShipPosition Then
                this.State(currentX, currentY) = GridState.Unknown
            End If
        Next
    Next
End Sub

Player

What is a player? What does it need to be able to do? We know a player will need to be associated with a game grid; we know a player can be human or computer-controlled. And if we break down the game into individual steps, we can tell we’ll need a player to be able to place a ship on its grid, and – given the enemy grid, be able to tell the game where it’s going to be shooting next. So we can already have an IPlayer interface that formalizes this contract:

'@Folder("Battleship.Model.Player")
'@Interface
Option Explicit

Public Enum PlayerType
    HumanControlled
    ComputerControlled
End Enum

'@Description("Identifies whether the player is human or computer-controlled.")
Public Property Get PlayerType() As PlayerType
End Property

'@Description("Gets the player's grid/state.")
Public Property Get PlayGrid() As PlayerGrid
End Property

'@Description("Places specified ship on game grid.")
Public Sub PlaceShip(ByVal currentShip As IShip)
End Sub

'@Description("Attempts to make a hit on the enemy grid.")
Public Function Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
End Function

The HumanPlayer implementation is rather boring – PlaceShip and Play do nothing. The AIPlayer implementation is much more interesting:

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "AIPlayer"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
'@Folder("Battleship.Model.Player")
Option Explicit
Implements IPlayer

Private Const Delay As Long = 800

Private Type TPlayer
    GridIndex As Byte
    PlayerType As PlayerType
    PlayGrid As PlayerGrid
    Strategy As IGameStrategy
End Type

Private this As TPlayer

Public Function Create(ByVal gridId As Byte, ByVal GameStrategy As IGameStrategy) As IPlayer
    With New AIPlayer
        .PlayerType = ComputerControlled
        .GridIndex = gridId
        Set .Strategy = GameStrategy
        Set .PlayGrid = PlayerGrid.Create(gridId)
        Set Create = .Self
    End With
End Function

Public Property Get Self() As IPlayer
    Set Self = Me
End Property

Public Property Get Strategy() As IGameStrategy
    Set Strategy = this.Strategy
End Property

Public Property Set Strategy(ByVal value As IGameStrategy)
    Set this.Strategy = value
End Property

Public Property Get PlayGrid() As PlayerGrid
    Set PlayGrid = this.PlayGrid
End Property

Public Property Set PlayGrid(ByVal value As PlayerGrid)
    Set this.PlayGrid = value
End Property

Public Property Get GridIndex() As Byte
    GridIndex = this.GridIndex
End Property

Public Property Let GridIndex(ByVal value As Byte)
    this.GridIndex = value
End Property

Public Property Get PlayerType() As PlayerType
    PlayerType = this.PlayerType
End Property

Public Property Let PlayerType(ByVal value As PlayerType)
    this.PlayerType = value
End Property

Private Property Get IPlayer_PlayGrid() As PlayerGrid
    Set IPlayer_PlayGrid = this.PlayGrid
End Property

Private Sub IPlayer_PlaceShip(ByVal currentShip As IShip)
    this.Strategy.PlaceShip this.PlayGrid, currentShip
End Sub

Private Function IPlayer_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Win32API.Sleep Delay
    Set IPlayer_Play = this.Strategy.Play(enemyGrid)
End Function

Private Property Get IPlayer_PlayerType() As PlayerType
    IPlayer_PlayerType = this.PlayerType
End Property

Notice the Play and PlaceShip methods aren’t actually implemented in the AIPlayer class; instead, we inject an IGameStrategy and that is what polymorphism allows us to do: we can now inject an instance of a class that implements a given strategy, and we can extend the game with another AI, without even changing a single line of existing AIPlayer code!

NewGame.png

VBA+OOP: What, When, Why

As I’m writing a series of articles about a full-blown OOP Battleship game, and generally speaking keep babbling about OOP in VBA all the time, it occurred to me that I might have failed to clearly address when OOP is a good thing in VBA.

OOP is a paradigm, which entails a specific way of thinking about code. Functional Programming (FP) is another paradigm, which entails another different way of thinking about code. Procedural Programming is also a paradigm – one where code is essentially a sequence of executable statements. Each paradigm has its pros and cons; each paradigm has value, a set of problems that are particularly well-adapted to it, …and its flock of religious zealots that swear they saw the Truth and that their way is The One True Way: don’t believe everything you read on the Internet – think of one (doesn’t matter which) as a hammer, another as a screwdriver, and the other as a shovel.

Don’t be on the “Team Hammer!” or “Team Screwdriver!”, or “Team Shovel!” – the whole (sometimes heated) debate around OOP vs FP is a false dichotomy. Different tools work best for different jobs.

So the first question you need to ask yourself is…

What are you using VBA for?

Scripting/Automation

If you’re merely scripting Excel automation, you very likely don’t need OOP. An object-oriented approach to scripting makes no sense, feels bloated, and way, way overkill. Don’t go there. Instead, a possible approach to cleaner code could be to write one macro per module: have a Public procedure at the top (your “entry point”), at a high abstraction level so it’s easy to tell at a glance everything it does – then have all the Private procedures it calls underneath, listed in the order they’re invoked, so that the module/macro essentially unfolds like a story, with the high-level bird’s eye view at the top, and the low-level gory details at the bottom.

The concept at play here is abstraction levels – see abstraction is one of the pillars of OOP, but it’s not inherently OOP. Abstraction is a very good thing to have in plain procedural code too!

Procedural Programming isn’t inherently bad, nor evil. Well-written procedural code at the right abstraction level is a pleasure to read, and when you think in terms of functions (i.e. inputs -> output) rather than “steps” or “instructions”, then you can write pure functions – and pure functions can (and probably should) be unit-tested, too.

If you’ve ever written a User-Defined Function that a worksheet invokes, you’ve likely written a pure function: it takes input, and produces output without accessing or altering any other state. If you’ve done that, congratulations, you’ve learned the fundamental building block of the Functional Programming paradigm! ..then again, pure functions aren’t inherently FP.

The vast majority of VBA code written, falls in this category. It would likely be toxic to try to squeeze OOP into such code; I’ll even say that OOP is flat-out the wrong approach here. However, an FP-like approach isn’t necessarily a bad idea… although, VBA clearly wasn’t designed with Functional Programming in mind, so you’ll hit the language’s limitations very early in the process… but it can’t hurt to design your script avoiding side-effecting functions and proliferating global state.

Framework/Toolbox Code

Somewhere in-between the script and the full-blown application, there’s this type of VBA project that you write for yourself as some kind of “toolbox” with all kinds of useful code that you often carry around and pretty much systematically import into every one of your new VBA projects.

This, in my opinion, is where OOP really shines the brightest in VBA: it doesn’t matter if it’s procedural programming code consuming these objects – it’s OOP nonetheless. As much as the Excel object model itself is made of objects, and couldn’t care less if it’s procedural or object-oriented code consuming it.

We could be talking about a fully-reusable ProgressIndicator class, some polymorphic Logger tool that the consuming code can configure as needed to log to the debugger, some text file, or a database, or a set of custom data type classes – a Stack, or an ArrayList wrapper, or a File class that wraps file I/O operations and maybe some Scripting.FileSystemObject functionality, or something else: you get the idea.

Full-Blown Applications

If you’re seeing VBA as a document-hosted VB6 (it pretty much literally is) that can do everything a VB6 program can do, then you’re looking at something else entirely – and the problems you’re solving are in a completely different realm: you’re not automating spreadsheets anymore: you’re writing a CRUD application to automate or facilitate data entry into your ERP system, or you’re maintaining a set of support tables in some corporate database, …likely, something a programmer would look at and ask “hey why are you doing this in VBA?”

“Because I can” is a perfectly acceptable answer here, although “because I have to” is often more likely. Regardless, it doesn’t matter: well-written VBA code is better than poorly-written VB.NET or C# code (or Java, or anything else): if you’re writing VB.NET and it says “Imports Microsoft.VisualBasic” at the top of your modules/classes, then you’re likely not writing idiomatic .NET code, you’re writing glorified VB6 using modern syntax, in a modern IDE.

Bad code is on the programmer, not the language.

When you’re making an application, procedural programming can be actively harmful – you’re building a complex system, using a paradigm that doesn’t scale well. FP would be an option for the bulk of the application logic, but then again VBA wasn’t made for Functional Programming. An Object-Oriented approach seems the most sensible option here.

But what about RAD?

Rapid Application Development software, such as Microsoft Access, blurs the lines: now you’re given a framework to write event-driven code (which does stem from OOP), but using object-oriented patterns (e.g. MVC) can feel like you’re working against that framework… which is never a good sign. The best approach here would be to embrace the framework, and to extract as much of the logic as possible into small/specialized, self-contained components that can be individually tested.

OOP Battleship Part 1: The Patterns

Battleship

About OOP

If you’ve been following this blog, you know that VBA is indeed very capable of “real” object-oriented code, regardless of what “real programmers” say about the language.

So far I’ve presented snippets illustrating patterns, and tiny example projects – the main reason I haven’t posted recently is, I’ve been busy writing a VBA project that would illustrate everything, from factory methods to unit testing and Model-View-Controller architecture. In this blog series, you will discover not only that VBA code can be very elegant code, but also why you would want to take your skills up to the next level, and write object-oriented code.

You may have been writing VBA code for well over a decade already, and never felt the need or saw a reason to write your code in class modules. Indeed, you can write code that works – OOP will not change that. At one point or another you may find yourself thinking “well that’s nice, but I’ll never need to do any of this” – and you very well might be completely right. Think of OOP as another tool in your toolbox. OOP isn’t for throw-away code or small, simple projects; OOP is for large projects that need to scale and be maintained over the years – projects you would show to a programmer in your IT department and they’d go “but why are you doing this in Excel/VBA?” …and of course the reason is “because that’s the only tool you guys are letting me use!” – for these projects (and they exist, and they’re mission-critical in every business that have them!), the structure and architecture of the code is more important than its implementation details; being easy to extend is more important than everything else: these projects are the projects that will benefit the most from OOP.

Object-Oriented VBA code is much easier to port to another language than procedural VBA code, especially with proper unit test coverage – which simply can’t be done with traditional, procedural code. In fact, OOP VBA code reads very, very much like plain VB.NET, the only difference being the syntactic differences between the two languages. If your mission-critical VBA project ever falls in the hands of your IT department, they will be extremely grateful (not to mention utterly surprised) to see its components neatly identified, responsibilities clearly separated, and specifications beautifully documented in a thorough test suite.

Is OOP necessary to make a working Battleship game in VBA? Of course not. But taking this Battleship game as a fun metaphor for some business-critical complex application, OOP makes it much easier to make the game work with the human player on Grid1 just as well as on Grid2, or making it work with an AI player on both Grid1 and Grid2, or making different difficulty levels / strategies for the AI player to use, or trashing the entire Excel-based UI and making the game work in Word, Access, or PowerPoint, or all of the above… with minimal, inconsequential changes to the existing code.

Any of the above “changing requirements” could easily be a nightmare, even with the cleanest-written procedural code. As we explore this project, you’ll see how adhering to the SOLID OOP principles makes extending the game so much easier.

But before we dive into the details, let’s review the patterns at play.


PredeclaredId / default instance

I’ve covered this before, but here’s a refresher. I find myself using this trick so often, that I’ve got a StaticClass.cls class module readily available to import in any project under my C:\Dev\VBA folder. The file looks like this:

VERSION 1.0 CLASS
BEGIN
MultiUse = -1 'True
END
Attribute VB_Name = "StaticClass1"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
Option Explicit

The VB_PredeclaredId = True attribute is the important part. With this attribute on, the class now has a default instance. What’s critical is to avoid storing instance state in this default instance (see UserForm1.Show). But for pure functions such as factory methods, it’s golden.

Under the hood, every single object is given an ID: when you New up a class, you create a new object ID. When a class has this attribute set to True, VBA automatically pre-declares an ID for an object that’s named after the class itself.

Interfaces

Perhaps the single most powerful (yet underused) feature of VBA: the Implements keyword makes an instance of a class able to present different public interfaces to its clients. This allows us to have public mutators on a class, and yet only expose public accessors to client code that is written against an interface. More on that below.

Think of an interface as a 110V power outlet.

449px-nema_5-15_outlet_120v-15a

It doesn’t care what it’s powering, so long as it fulfills the contract: any device that operates on a standard North American 110V power outlet can be plugged into it, and it’s just going to work, regardless of whether it’s a laptop, a desktop, a monitor, or a hairdryer.

An interface is a contract: it says “anything that implements this interface must have a method that does {thing}”, without any restrictions on how that {thing} is actually implemented: you can swap implementations at any given time, and the program will happily work with that implementation, unaware and uncaring of the implementation details.

This is a very powerful tool, enabling polymorphism – one of the 4 pillars of OOP. But strictly speaking, every single object exposes an interface: its public members are its interface – what the outside world sees of them. When you make a class implement an interface, you allow that class to be accessed through that interface.

Say you want to model the concept of a grid coordinate. You’ll want to have X and Y properties, …but will you want to expose Public Property Let members for these values? The GridCoord class can very well allow it, and then the IGridCoord interface can just as well deny it, making code written against IGridCoord only able to read the values: being able to make something read-only through an interface is a very desirable thing – it’s the closest we can get to immutable types in VBA.

In VBA you make an interface by adding a class module that includes stubs for the public members you want to have on that interface. For example, this is the entire code for the IPlayer interface module:

'@Folder("Battleship.Model.Player")
Option Explicit

Public Enum PlayerType
HumanControlled
ComputerControlled
End Enum

'@Description("Gets the player's grid/state.")
Public Property Get PlayGrid() As PlayerGrid
End Property

'@Description("Identifies the player class implementation.")
Public Property Get PlayerType() As PlayerType
End Property

'@Description("Attempts to make a hit on the enemy grid.")
Public Function Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
End Function

'@Description("Places specified ship on game grid.")
Public Sub PlaceShip(ByVal currentShip As IShip)
End Sub

Anything that says Implements IPlayer will be required (by the VBA compiler) to implement these members – be it a HumanPlayer or a AIPlayer.

Here’s the a part of the actual implementation for the AIPlayer:

Private Sub IPlayer_PlaceShip(ByVal currentShip As IShip)
this.Strategy.PlaceShip this.PlayGrid, currentShip
End Sub

Private Function IPlayer_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
Set IPlayer_Play = this.Strategy.Play(enemyGrid)
End Function

The HumanPlayer class does something completely different (i.e. it does nothing / lets the view drive what the player does), but as far as the game is concerned, both are perfectly acceptable IPlayer implementations.

Factory Method

VBA doesn’t let you parameterize the initialization of a class. You need to first create an instance, then initialize it. With a factory method on the default instance (see above) of a class, you can write a parameterized Create function that creates the object, initializes it, and returns the instance ready to use:

Dim position As IGridCoord
Set position = GridCoord.Create(4, 2)

Because the sole purpose of this function is to create an instance of a class, it’s effectively a factory method: “factory” is a very useful OOP pattern. There are several ways to implement a factory, including making a class whose sole responsibility is to create instances of another object. When that class implements an interface that creates an instance of a class that implements another interface, we’re looking at an abstract factory – but we’re not going to need that much abstraction here: in most cases a simple factory method is all we need, at least in this project.

Public Function Create(ByVal xPosition As Long, ByVal yPosition As Long) As IGridCoord
With New GridCoord
.X = xPosition
.Y = yPosition
Set Create = .Self
End With
End Function

Public Property Get Self() As IGridCoord
Set Self = Me
End Property

The GridCoord class exposes Property Let members for both the X and Y properties, but the IGridCoord interface only exposes Property Get accessors for them – if we consistently write the client code against the “abstract” interface (as opposed to coding against the “concrete” GridCoord class), then we effectively get a read-only object, which is nice because it makes the intent of the code quite explicit.

Model-View-Controller

This architectural pattern is extremely widespread and very well known and documented: the model is essentially our game data, the game state – the players, their respective grids, the ships on these grids, the contents of each grid cell. The view is the component that’s responsible for presenting the model to the user, implementing commands it receives from the controller, and exposing events that the controller can handle. The controller is the central piece that coordinates everything: it’s the component that tells the view that a new game should begin; it’s also the component that knows what to do when the view says “hey just so you know, the user just interacted with cell F7”.

So the controller knows about the model and the view, the view knows about the model, and the model knows nothing about no view or controller: it’s just data.

Adapter

The adapter pattern is, in this case, implemented as a layer of abstraction between the controller and the view, that allows the former to interact with anything that implements the interfaces that are required of the latter. In other words, the controller is blissfully unaware whether the view is an Excel.Worksheet, a MSForms.Userform, a PowerPoint.Slide, or whatever: as long as it respects the contract expected by the controller, it can be the “view”.

Different view implementations will have their own public interface, which may or may not be compatible with what the controller needs to work with: quite possibly, an electronic device you plug into a 110V outlet, would be fried if it took the 110V directly. So we use an adapter to conform to the expected interface:

adapter

Or you may have taken your laptop to Europe, and need to plug it into some funny-looking 220V outlet: an adapter is needed to take one interface and make it compatible with another. This is quite literally exactly what the adapter pattern does: as long as it implements the IViewCommands interface, we can make the controller talk to it.

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.