Globals and Ambient Context

Most of the time, we don’t need any global variables. State can usually be neatly encapsulated in an object, and a reference to this object can easily be passed as an argument to any procedure scope that needs it. But global scope is neither a necessary evil, nor necessarily evil. Like many things in programming, it’s a tool, and like many other tools, misusing it can cause pain.

The VBA code and host Excel workbook accompanying this article can be found on GitHub.


What is Global Scope?

When we declare a variable inside a procedure, we call it a “local variable” in reference to its scope being local to the procedure. “Module variables” are accessible within any procedure scope within the module they’re declared in. Public members of private modules (and Friend members of public modules) are only accessible within the project they live in, and Public members of public modules are global and can be accessed from other projects.

The different scopes of VBA: Global, project, module, and local.

Because in VBA class modules are private by default, and a public class is only PublicNotCreatable (as in, a referencing project cannot create a New instance of a class, factory methods must be provided), and also because “actually global” is in reality slightly more complicated than that (the VB_GlobalNamespace attribute is always going to be False for a VBA class), for the sake of simplicity when I talk about “global scope” and “globals” in this article, I’m treating global and project scopes as one and the same – but it’s important to know the difference, especially more so in scenarios where a VBA/Excel add-in/library is being referenced by other VBA projects, where a tidy public API is handy.

Keywords
Rubberduck recommends using the Dim keyword only in local scope, and to use the Private keyword to declare module-level variables. It also recommends using Public over Global, because nothing is really “global” in VBA and that makes the deprecated keyword potentially confusing. The Global keyword really means Public in VBA, and should be avoided.

Picture the VBA runtime executing some macro procedure and some variable needs to be incremented by 1. Scope determines whether that variable identifier is referring to a local, module, or global declaration. Accessibility is how we use code to restrict scope, using keywords like Private, Public, or Friend: if the variable identifier exists in a public module but is declared with the Private keyword, then it’s inaccessible and not in scope for the procedure we’re in.

So in search for the variable’s declaration we look for a local scope declaration by that name. If there isn’t any, we look for a module scope declaration for that name. Not there? We look at everything we can see in project scope. If we still haven’t found it then, we look for the declaration in the referenced libraries and projects, in priority order (so, the VBA standard library, then the host application’s own object model library, then everything else).

That’s scoping. Scopes and accessibility are closely related, but they’re different things. Think of accessibility as a tool to shape your private and public interfaces and APIs, keeping in mind that in VBA all module members are implicitly Public unless their declaration states otherwise.


Globals and Testability

Global variables are very useful: having a piece of data that is accessible from anywhere in the code does have its advantages. Used wisely, globals can very elegantly address cross-cutting concerns. Instead of having every method responsible for its own logging, or instead of passing a Logger instance to every method, each scope can access a single global Logger object (or invoke the same Log utility procedure), and there really isn’t any problem with that, …until you realize that your unit tests are all needlessly writing logs to some file under C:\Dev\VBA because the global logger is doing its job whether or not the code invoking it is being executed from a test runner… and this is making tests run code that isn’t related to these tests’ purpose: if there’s a bug in the logger code, it’s a test about the logger code that should be failing, not every single other test that couldn’t care less for the logging functionality.

From a testability standpoint, code with global dependencies can be difficult, if not impossible to test. In the case of a global Logger dependency, the logger’s interface would need to expose some kind of “kill switch” that tests can invoke to disable logging… but then modifying an otherwise perfectly good interface for the sake of making the object aware of whether it’s being invoked from a test or not, isn’t ideal at all (we’ll see why in a bit).

This Logger is a good example of a legitimate global service, but it’s “user code” that could always be pragmatically modified to accommodate testing. What about code that depends on global-scope services that aren’t “user code”?

Treating the Excel Object Model as a Dependency

Imagine needing to write tests for user-defined functions (UDF) that store a number of values in a global Dictionary and then schedule a macro that then runs (asynchronously!) and sends these values over to some web API that returns data that then ends up on the worksheet, underneath the calling UDF; the functions have dependencies on Application.Caller and Application.OnTime: we don’t own the Application global object, and we can’t modify its code to accommodate testing – what then?

Writing tests for a UDF is normally trivial: the function takes inputs, computes a result, and then returns it. Tests can supply various inputs and run the function through all kinds of cases and assert that it handles them correctly, by simply comparing its return value with what’s expected, and exceptional edge cases can have tests asserting that the expected error is thrown.

Writing tests for a side-effecting UDF that temporarily stores data in global scope is a lot more challenging, for many reasons. Remember, unit tests:

  • Should reliably produce the same outcome regardless of any external factors;
  • Should be fast, and not involve any I/O or network activity;
  • Should be able to be executed individually or in any given order without affecting outcome;
  • Should be able to be executed concurrently (at least in theory – VBA won’t run concurrent code).

With state shared between the tests, we have to be careful to correctly setup and clean-up that state before & after each test, so that each test gets a fresh canvas in a controlled environment… and then we can live with VBA unit tests that would likely break if executed concurrently, because VBA can’t run them concurrently anyway.


Testing Untestable Things

Back to this not-so-crazy UDF scenario with the Application.OnTime hack: it wouldn’t be acceptable for a test to literally wait for Excel to decide it’s time to invoke a macro, not any more than a test should be sending any actual HTTP requests (although that would be very a good way to actually be testing an API’s rate limits and get acquainted with throttling, I guess), let alone parse and process an actual HTTP response.

Such a user-defined function involves too many moving parts soldered together to be testable: making the code testable involves making the parts moving parts again, and yes it involves a proverbial blowtorch and lots of proverbial sparks flying everywhere.

Refactoring code to make it testable is a lot of fun, but the first step is, ideally, to fully grasp what’s going on and why.

If you aren’t familiar with using Application.OnTime in user-defined functions (only indirectly, because Application.OnTime calls, like run-time errors and many other members in the Excel object model, get “swallowed” when Excel is evaluating a UDF), it’s a pretty cool process that goes like this:

The calling cell contains the UDF’s return value just before the macro gets asynchronously invoked and produces its own output.

So if a UDF stored its arguments as key/value pairs in a global-scope dictionary, if all goes well and according to plan, the macro that runs a moment later gets to consume this data.

By storing the Application.Caller cell object reference in global scope, the side-effecting macro gets to know where to put its results table. There’s always the possibility that a second UDF overwrites this global state during the split-second between the moment a first UDF writes it and the moment the scheduled asynchronous read of this global state actually happens: it’s important to keep in mind that Ambient Context does not inherently address this particular problem; the state is still global and mutable from anywhere in the code, and there is never any guarantee that any scope will run to completion before the VBA runtime decides it’s an asynchronous callback’s turn to run.

The Application.Caller member isn’t going to return a Range reference when it’s not a worksheet cell invoking the function, we can’t afford to wait for Application.OnTime, and we’d like to avoid actually invoking any Win32 API functions during a test. That UDF simply isn’t testable as-is.

The solution is to introduce an abstraction to wrap the Application members we need, and make the side-effecting UDFs depend on that abstraction instead of invoking Application members directly.

AbstractionThe untestable code might look something like this:

Public Function SideEffectingUDF(ByVal FirstParameter As String, ByVal SecondParameter As Long) As Variant
    Set SomeGlobalRange = Application.Caller.Offset(RowOffset:=1)
    With SomeGlobalDictionary
        .Clear
        .Add "FirstParameter", FirstParameter
        .Add "SecondParameter", SecondParameter
    End With
    ScheduleMacro
End Function

Where ScheduleMacro involves a Win32 API call to schedule the execution of an Execute procedure that handles the Application.OnTime scheduling of the actual side-effecting procedure.

We want to be able to write a test that invokes this SideEffectingUDF function, and determines whether Application.Caller was invoked: Application.Caller is a dependency here, and for the test to be able to fulfill its purpose we must find a way to inject the dependencies so they can be controlled by the test, from outside the function.

Note how narrow such a test would be: it asserts that the UDF gets the Application.Caller reference, nothing more. Other tests would be similarly narrow, but for other things, and we don’t want a failing Application.Caller member call to interfere with these other tests by throwing error 91 before the test gets to do its thing. Whether or not we need to know if a UDF does or does not invoke Application.Caller, we still need a way to abstract the dependency away, to stub it.

You may be thinking “oh that’s easy” and be tempted go down this path:

Public Function SideEffectingUDF(ByVal FirstParameter As String, ByVal SecondParameter As Long) As Variant
    If TypeOf Application.Caller Is Excel.Range Then
        ' caller is a worksheet cell
        Set ThatGlobalCell = Application.Caller.Offset(RowOffset:=1)
        With ThatGlobalDictionary
            .Clear
            .Add "FirstParameter", FirstParameter
            .Add "SecondParameter", SecondParameter
        End With
        ScheduleMacro "SideEffectingMacro"
    Else
        ' caller is a unit test
        Set ThatGlobalCell = Sheet1.Cells(1, 1) ' tests can read as "Application.Caller was invoked"
        With ThatGlobalDictionary
            .Clear
            .Add "FirstParameter", FirstParameter
            .Add "SecondParameter", SecondParameter
        End With
        SideEffectingUDF = True ' tests can read this as "macro was scheduled"
    End If
End Function

While it does solve the problem of avoiding to involve Application.Caller and actually scheduling the macro in tests, there are several reasons why this is a terrible idea:

  • Function now has a higher Cyclomatic Complexity metric by virtue of now needing more execution paths to accomplish the same thing: the code is objectively and measurably more complex now, on top of being repetitive (copying & pasting any code is usually a sign something is off!).
  • Tests are no longer executing the same code as normal execution does, which means tests are now testing code that only exists because there are tests: the normal execution path remains untested, and that makes the tests worthless busy-work.
  • Tests now need to be making assumptions about how the function is implemented, which effectively casts the code into concrete instead of making it simpler & safer to modify.
  • Dependencies should be abstractions, and code should be working with these abstractions without regards to their actual implementation: code that acts differently when the runtime type of an abstraction is X vs when it’s Y, violates the Liskov Substitution Principle, the “L” of “SOLID” that essentially states that all implementations of a given abstraction should be treated the same.

The killer is the second bullet: if the sole purpose of a test is to determine whether Application.Caller was invoked, and the UDF says “oh we’re in a test, here yeah everything is all right, see”, then a UDF that does nothing but returning True would pass that test, and that is why the test is useless, as is the code duplication.

When we write a test whose purpose is to determine whether the Application.Caller dependency was invoked, the test should FAIL when it isn’t, otherwise that test is just as good as a deleted one.

Now picture the UDF looking like this instead:

Public Function SideEffectingUDF(ByVal FirstParameter As String, ByVal SecondParameter As Long) As Variant
    With AppContext.Current
        Set .Target = .Caller.Offset(RowOffset:=1)
        .Property("FirstParameter") = FirstParameter
        .Property("SecondParameter") = SecondParameter
        .ScheduleMacro
    End With
End Function

The UDF now only has one dependency, AppContext.Current, which is global state by virtue of being accessible from the default instance of the AppContext class; we’re tightly coupled with the AppContext class, but only because we specifically want to access global state in a controlled manner, and the rest of the function is working against the IAppContext abstraction. The state that was formerly a Range and a Dictionary globally-scoped declaration is now properly encapsulated in an object, and the “current” AppContext is coming into existence from outside the UDF scope (but still from within our own code), which is exactly what we want: now unit tests get to inject a TestContext instead of manipulating global state.

So how do we get there?


Implementation

The basic idea is to pull our dependencies from global scope, encapsulate them in a class module, …and then making an instance of that class an “ambient context” that’s still globally accessible, but that introduces the necessary abstraction needed to make that UDF fully testable.

We want to leverage the default instance of the AppContext class, so we’re going to need an AppContext class with a @PredeclaredId annotation and a Current property getter that returns some IAppContext instance. If you’re familiar with factory methods this will feel a bit like something you’ve already seen:

'@PredeclaredId
Option Explicit
Implements IAppContext
Private Type TState
    Factory As IAppContextFactory
    Current As IAppContext
    '...    
End Type
Private This As TState
'@Description "Gets the current (or default) context."
Public Property Get Current() As IAppContext
    Errors.GuardNonDefaultInstance Me, AppContext, TypeName(Me)
    
    If This.Current Is Nothing Then
        Set This.Current = This.Factory.Create
        Errors.GuardNullReference This.Factory, TypeName(Me), "IAppContextFactory.Create returned Nothing."
    End If
    
    Set Current = This.Current
End Property
Private Property Get IsDefaultInstance() As Boolean
    IsDefaultInstance = Me Is AppContext
End Property
Private Sub Class_Initialize()
    If IsDefaultInstance Then
        'must initialize context with sensible defaults:
        Set This.Factory = New AppContextFactory
        Set This.TimerProvider = New TimerProvider
    Else
        Set This.Properties = New Scripting.Dictionary
        'we want all instances to have the same provider instance:
        Set This.TimerProvider = AppContext.TimerProvider
    End If
End Sub

We don’t normally want Property Get procedures to be side-effecting, but with an Ambient Context what we want is to yield a cached instance of the context class, so when no instance already exists, the getter caches the created object so it’s readily available next time, making it accessible from anywhere in the project (aka “global”).

Abstract Factory

The default instance of the AppContext class does not know what the actual runtime type of the Current context is, and this polymorphism is the cornerstone making it all work: the Current property getter is responsible for caching the new context instance, but not for actually creating it. That’s the job of an abstract factory (the IAppContextFactory dependency) that we conveniently initialize to a concrete factory type that creates instances of… the AppContext class.

Why involve an abstract factory to create an instance of the class we’re in, you might ask? Because that’s only the default implementation, and with ability to Set the Factory reference from outside the class, tests can inject a different factory implementation, say, this one named TestContextFactory:

'@Folder "Tests.Stubs"
'@ModuleDescription "A factory that creates TestContext instances."
Option Explicit
Implements IAppContextFactory
Private Function IAppContextFactory_Create() As IAppContext
    Set IAppContextFactory_Create = New TestContext
End Function

Meanwhile the actual UDFs would be using this AppContextFactory implementation by default:

'@Folder "AmbientContext"
'@ModuleDescription "A factory that creates AppContext instances."
Option Explicit
Implements IAppContextFactory
Private Function IAppContextFactory_Create() As IAppContext
    Set IAppContextFactory_Create = New AppContext
End Function

The AppContext.Current property will happily cache an instance of any class whatsoever, as long as it implements the IAppContext interface. The abstract factory pattern allows us to spawn an instance of a class at run-time, of which we don’t necessarily know the actual “concrete” type at compile-time.

In other words just by reading the UDF code, there is no way to tell whether AppContext.Current is going to be an AppContext or a TestContext instance, and that is exactly what we want.

What this abstraction achieves, is the decoupling that is necessary for a test to be able to inject a TestContextFactory and take control of everything UDFs can do with an IAppContext object.

Context State

We know the context needs to wrap Application.Caller and Application.OnTime functionality. We know we need a Target cell, we need some Properties in an encapsulated Scripting.Dictionary. If we crammed all that into a single interface, we would get a somewhat crowded IAppContext interface that doesn’t quite adhere to the Interface Segregation Principle and Open/Closed Principle guidelines.

By abstracting away the macro-scheduling functionality into its own IAppTimer interface, and making that interface an abstract dependency of the context class, we can stub that abstract dependency and write tests for the logic of the context class itself. Without this extra step, the context can be stubbed to test the code that uses it, but the macro-scheduling bits would remain untestable.

Treating IAppTimer as a dependency of the context makes the IAppContext interface look like this:

'@Folder "AmbientContext.Abstract"
'@ModuleDescription "Encapsulates the data and macro invocation mechanism for a side-effecting UDF."
'@Interface
Option Explicit
'@Description "Gets the cell that invoked the currently-running user-defined function (UDF), if applicable; Nothing otherwise."
Public Property Get Caller() As Range
End Property
'@Description "Gets or sets the target reference cell that the side-effecting macro shall use."
Public Property Get Target() As Range
End Property
Public Property Set Target(ByVal Value As Range)
End Property
'@Description "Gets or sets a named value representing data passed between the UDF and the side-effecting macro."
Public Property Get Property(ByVal Name As String) As Variant
End Property
Public Property Let Property(ByVal Name As String, ByVal Value As Variant)
End Property
'@Description "Gets an array of all property names."
Public Property Get Properties() As Variant
End Property
'@Description "Gets or sets the IAppTimer dependency."
Public Property Get Timer() As IAppTimer
End Property
Public Property Set Timer(ByVal Value As IAppTimer)
End Property
'@Description "Clears all held state."
Public Sub Clear()
End Sub

Note that we’re not exposing the dictionary itself: rather we expose an indexed property to get/set the key/values, then by exposing the dictionary keys, the calling code gets to do everything it needs to do, without ever directly interacting with a Scripting.Dictionary, a bit as if the AppContext class were a custom collection.

Now, there’s something special about the IAppTimer dependency: we absolutely cannot have each context instance spawn timers willy-nilly, because a leaking Win32 timer is a nice way to send Excel up in flames. Yet, we need each context instance to be able to access the same IAppTimer reference.

A good way to solve this is by introducing a Provider mechanism. The interface looks like this:

'@ModuleDescription "A service that ensures all clients get the same IAppTimer instance."
'@Interface
Option Explicit
'@Description "Gets an IAppTimer instance."
Public Property Get Timer() As IAppTimer
End Property

What I’m calling a “provider” here is exactly the same mechanism that provides the IAppContext instance (a Property Get procedure that gets a cached object or creates the object and caches it), except no abstract factory needs to get involved here. The class also makes a very convenient place to put the name of the Win32 callback macro procedure:

Option Explicit
Implements ITimerProvider
Private Const MacroName As String = "Execute"
Private Property Get ITimerProvider_Timer() As IAppTimer
    Static Instance As AppTimer
    If Instance Is Nothing Then
        Set Instance = New AppTimer
        Instance.MacroName = MacroName
    End If
    Set ITimerProvider_Timer = Instance
End Property

TimerProvider the only object that creates a New AppTimer: as a result, every AppContext instance created from this factory is going to use the same IAppTimer reference, and if we need to write tests for AppContext we can inject a TestTimerProvider that returns a TestTimer.

Note that the “provider” mechanism is an implementation detail of AppContext: the TestContext doesn’t need this, because it just initializes itself with a TestTimer, while AppContext initializes itself with a TimerProvider that gets the IAppTimer instance. Being an implementation detail, there’s no ITimerProvider dependency on the abstract interface.


The Tests

The previously-untestable user-defined functions now look like this:

Public Function TestUDF(ByVal SomeParameter As Double) As Boolean
    On Error GoTo CleanFail
    
    With AppContext.Current
        
        Set .Target = .Caller.Offset(RowOffset:=1)
        .Property("Test1") = 42
        .Property("Test2") = 4.25 * SomeParameter
        .Timer.ExecuteMacroAsync
        
    End With
    
    TestUDF = True
CleanExit:
    Exit Function
CleanFail:
    TestUDF = False
    Resume CleanExit
    Resume
End Function

The code isn’t very far off from the original, but now we can write a test that passes when a UDF invokes the Caller member; when the UDF is invoked from a worksheet cell, IAppContext.Caller returns the Range reference returned by Application.Caller; when the exact same code is invoked from a test, IAppContext.Caller returns a bogus/test cell reference.

Similarly, when a UDF invokes IAppTimer.ExecuteMacroAsync, a Win32 API call schedules the execution of a callback macro that itself invokes Application.OnTime to schedule the execution of a side-effecting macro that can consume the state and alter the target range and worksheet; when the exact same code is invoked from a test, IAppTimer.ExecuteMacroAsync simply notes that it was invoked, …and does nothing else.

This test passes when IAppTimer.ExecuteMacroAsync is invoked from a UDF, and would fail if the UDF didn’t invoke it:

'@TestMethod("Infrastructure")
Private Sub TestUDF_SchedulesMacro()
    'inject the test factory:
    Set AppContext.Factory = New TestContextFactory
    
    'get the test context:
    Dim Context As TestContext
    Set Context = AppContext.Current
    
    'test factory already stubbed the timer:
    Dim StubTimer As TestTimer
    Set StubTimer = AppContext.Current.Timer
    
    'run the UDF:
    Dim Result As Boolean
    Result = Functions.TestUDF(0)
    
    'Assert that the UDF has invoked IAppContext.ScheduleMacro once:
    Const Expected As Long = 1
    Assert.AreEqual Expected, StubTimer.ExecuteMacroAsyncInvokes, "IAppTimer.ExecuteMacroAsync was invoked " & StubTimer.ExecuteMacroAsyncInvokes & " times; expected " & Expected
End Sub

Cohesion

Ambient Context is a fantastic tool to address cross-cutting concerns and leverage global scope in a way that does not hinder testing. It’s also useful for storing state and dependencies that would otherwise be held in global scope, when passing that state and dependencies as normal parameters isn’t possible.

That makes it a somewhat dangerous pattern: one must keep in mind that the state is still global, and globals that don’t need to be global, should not be global. By defining an explicit interface for the context (like IAppContext), we not only end up with neat abstractions: we also make it harder for the context interface to grow new members and for the class to become an over-engineered Globals.bas module.

Interfaces shouldn’t be designed to change. In .NET the IDisposable interface only mandates a parameterless Dispose method; IEquatable is all about an Equals method. A factory interface shouldn’t need more than a carefully parameterized Create method that only takes arguments that can’t be dependencies of the factory instance: we want to avoid modifying existing interfaces as much as possible, and since none of us can really predict the future… the best way to do that is to keep interfaces as slim as possible. Cohesion is what we’re after: a module that is cohesive will feel like everything is exactly where it should be.

If the members of a module don’t feel like they’re a cohesive and complete group of closely related methods, there’s a greater chance that more members need to be added in the future – and you will want to avoid that. Of course the “and complete” part can mean a few growing pains, but in general naming things is a great way to avoid the pitfalls of treating the context as some “state bag” where we just lazily stuff state without thinking it through. In that sense AppContext is probably one of the worst possible names for this: perhaps a FunctionContext that only exposes the Caller member would be a cleaner approach?

In the real world, ambient context is for things like System.Threading.Thread.CurrentThread in .NET: it’s very specialized, with a very specific purpose, and we don’t see it very often. Authorization mechanisms might use it too.

In VBA-land, I’ve never once needed to implement it until I came upon this side-effecting UDF scenario needing unit tests; macros are definitely much simpler to refactor for testability!

From Macros to Objects: The Command Pattern

In procedural code, a macro might be implemented in some Public Sub DoSomething procedure that proceeds to do whatever it is that it needs do, usually by dereferencing a number of library-defined objects and invoking their members in a top-to-bottom sequence of executable instructions. Clean, nicely written and well-modularized procedural code would have that be a small, high-abstraction public procedure at the top of some SomethingMacro standard module, with increasingly lower-abstraction private procedures underneath.

Looking only at scope names (the private procedures might be Function, and they would likely take parameters), the module for a MakeSalesReport macro might roughly look something like this:

Like “making coffee”, the phrase “make the sales report” is abstracting away quite a lot of smaller sub-steps.

Breaking down a problem into smaller and simpler steps and sub-steps is how we begin to achieve separation of concerns: maybe one of these sub-steps is going to require prompting the user for a filename – if that’s implemented in a separate PromptFileName function that’s only responsible for prompting the user for a filename, then it’s much easier to later (as needed) reuse that function by pulling it into its own, say, Files module, and making it Public.

If programming is a lot like writing a story, then procedures have to be the verbs we use to express the actions carried by our code. The smaller a procedure, the less it can do; the fewer things a procedure does, the easier it is to give it a name that accurately, precisely describes what it does.

Public Sub DoSomething()
    'do stuff:
    '...
    
    'get the filename:
    Dim FileName As String
    FileName = ...

    'do more stuff:
    '...

End Sub

Any chunk of code that can be isolated inside a procedure scope and described with a comment that essentially says “this chunk of code reticulates splines” (whatever that is – maybe it’s “get the filename:”, or a much less subtle “======= GET FILENAME =======”), is a chunk of code that could be extracted into its own ReticulateSplines named procedure scope, and then doing this replaces a comment that says “this chunk of code reticulates splines” and the entire code block that goes with it, with a higher-abstraction single procedure call that plainly says ReticulateSplines: by properly naming the things we abstract away, we can make our code expressive and [for the most part] self-explanatory.

Option Explicit

Public Sub DoSomething()
    DoStuff
    
    Dim FileName As String
    FileName = ...

    DoMoreStuff FileName

End Sub

Private Sub DoStuff()
'...
End Sub

Private Sub DoMoreStuff(ByVal FileName As String)
'...
End Sub

And that’s glorious already.

With object-oriented programming (OOP), we get to further increase the abstraction level, such a Public Sub DoSomething macro procedure might belong to some Macros or EntryPoints standard module, painting an abstract broad-brush big picture… with all the spline-reticulating gory details in Private procedures of a separate class module.

Like procedures in procedural code, classes in OOP become another building block to tell our story: with class modules we get to use nouns: procedures do things, objects are things. So we could have a SomeMacro class that encapsulates everything “do something” needs to do, and when we need a DoSomethingElse macro we can implement it in its own dedicated class module too, leaving the Macros module (or EntryPoints, or whatever… just not Module1!) a high-abstraction, broad-brush picture of what’s going on.

This boils down to 1) create the dependencies of the macro class module we want to create; 2) create and initialize the “macro” object, and 3) invoke a Run method to, well, run the macro.

A standard module doing that, might look like this:

Option Explicit
Private Const ConnectionString As String = "..."

Public Sub DoSomething()
    ' create the dependencies...
    Dim DbService As IDbService
    Set DbService = SomeDbService.Create(ConnectionString)

    ' create the macro object, pass/inject the dependencies;
    ' we know SomeMacro needs a Worksheet and an IDbService
    ' because its Create factory method takes them as parameter:
    With SomeMacro.Create(Sheet1, DbService)
        .Run ' runs the macro
    End With
End Sub

Public Sub DoSomethingElse()
    'we could have another macro here...
    '..if that other macro is in another class...
    '...does it have a .Run method?
End Sub

This does effectively roughly demonstrate Dependency Injection and Inversion of Control in VBA (glossing over the required predeclared ID hidden attributes here), but in the context of this article, the point of interest is the .Run member call: if we make an object that encapsulates the notion of running a macro, it makes sense for that object to have a Run method. However if we don’t formalize this concept with an interface, we could have a SomeMacro.Run, then we could have AnotherMacro.Execute, and why not SomeOtherMacro.DoSomething: nothing is structuring things and telling the compiler and future maintainers “see this class is a macro and it has a method that runs it”, so while it’s nice that we’ve nicely cleaned up the Macros module by moving most of the code into class modules, it’s still chaos out there – unless there’s a way to get all macros to agree on exactly how we run them.

How do we tell the compiler “this class is a macro and it has a method that runs it”?

Interfaces and the Implements keyword, of course!

We can do this by adding a new class module (call it IMacro – I’m really not a prefix guy, but abstract interfaces in COM traditionally have that I prefix, and the tradition carried into C# and .NET, so here we are – if this were Java I would have just called it Macro; it’s all just conventions), and then adding a Run method with an empty body – this class shall remain abstract, and the implementation(s) shall be provided by other class modules:

'@ModuleDescription "Represents an executable macro."
'@Interface
Option Explicit

'@Description "Runs the macro."
Public Sub Run()
End Sub

The implementation(s) would be class modules with Implements IMacro and a Private Sub IMacro_Run procedure that invokes a Run procedure which… would break down into smaller, lower-abstraction private procedures underneath, and would delegate the more specialized work to more specialized objects (which would thus become that class’ dependencies). Sounds familiar?

Yep. You’re looking at your standard procedural macro, with the only difference being that instead of a standard module it’s now inside a class module that Implements IMacro.

Is this… a command pattern (macro in a class module)? Turns out, it pretty much actually is!

Of course, that’s not the whole story. But yes, it’s indeed a command pattern, however minimal – in design pattern abstraction terminology:

  • the caller is the Public Sub DoSomething macro procedure
  • the command is the IMacro interface
  • the concrete command is the SomeMacro class (implements IMacro)
  • the SomeDbService dependency would be a receiver, I think

What makes a “macro in a classs module” a command pattern, is the IMacro interface and how it abstracts the notion of “running a macro”. It represents the abstract concept of “something that can run”, and this right there, is the command pattern in a nutshell.

Let’s dig a little deeper though, because VBA can do much more than just macros, and commands are everywhere in software.

Divide & Conquer

Say we’re writing a user interface that can add, delete, and update records in a table. We might have a form featuring a ListBox control, and then CommandButton controls to create a new record, delete the selected one(s), and modify an existing one.

In a clean design without the command pattern, code might be written and organized with a “divide & conquer” attitude, and would look something like this (lower-abstraction details omitted, they’re not the point):

Option Explicit

'...

Public Property Get Model() As SomeModel
    'gets an object holding the data needed for this form.
End Property

Private Sub CreateNewItem()
    With New ItemEditorForm ' new form instance
        .Show 
        If .Cancelled Then Exit Sub
        AddToSource .Model ' implies the form has a Model As Something property.
    End With
End Sub

Private Sub AddToSource(ByVal Thing As Something)
    Model.AddThing Thing ' the Something class needs an AddThing method for this.
End Sub

Private Sub RemoveFromSource(ByVal Thing As Something)
    Model.RemoveThing Thing ' the Something class needs a RemoveThing method for this.
End Sub

Private Sub DeleteSelectedItems()
    Dim i As Long
    For i = Me.ItemsBox.ListCount - 1 To 0 Step -1 ' assumes an ItemsBox listbox
        If Me.ItemsBox.Selected(i) Then ' does not assume single-item selections
            Dim Item As Something
            ' assumes a ListSource collection of Something objects
            Set Item = ListSource(Me.ItemsBox.ListIndex)
            If Not Item Is Nothing Then
                RemoveFromSource Item  ' <~ do this work at a lower abstraction level
            End If
        End If
    Next
End Sub

Private Sub EditSelectedItem()
    Dim Item As Something
    Set Item = ListSource(Me.ItemsBox.ListIndex)
    If Item Is Nothing Then Exit Sub

    With New ItemEditorForm ' pop a modal with fields for an item...
        Set .Model = Item ' <~ this item. (assumes a Model As Something property)
        .Show
        If .Cancelled Then Exit Sub
        UpdateSourceItem .Model ' <~ do this work at a lower abstraction level
    End With
End Sub

Private Sub CreateButton_Click()
    CreateNewItem ' <~ do this work at a lower abstraction level
End Sub

Private Sub DeleteButton_Click()
    DeleteSelectedItems ' <~ do this work at a lower abstraction level
End Sub

Private Sub EditButton_Click()
    EditSelectedItem ' <~ do this work at a lower abstraction level
End Sub


'...

By factoring each button action into its own dedicated procedure, we get to name things and clearly split things up by functionality. The job of a Click handler becomes to fork execution elsewhere, so they [often] become simple one-liners invoking a private method, painting a broad-brush picture of what’s going on.

We could just as well implement the functionality in the body of the Click handler, but I personally find extracting these private methods worthwhile, because they make it easier to restructure things later (you can cut/move the entire scope), versus leaving that code in event handlers where the refactoring is more tedious. Event handlers are entry points in a way, enough so that having them at a high abstraction level feels exactly right for me.

Now what if we wanted the EditButton to only be enabled when only one item is selected, and then make the DeleteButton only enabled when at least one item is selected? We would have to start handling the ItemsBox.Change event, and would need additional code that might look like this:

Private Sub SetButtonsEnabledState()
    Me.EditButton.Enabled = (Model.SelectedItems.Count = 1)
    Me.DeleteButton.Enabled = (Model.SelectedItems.Count > 0)
    '...
End Sub

Private Sub ItemsBox_Change()
    SetModelSelectedItems
    SetButtonsEnabledState
End Sub

Imagine a form with many more controls – each with their own “is enabled” rules and a Change event handler procedure: boilerplate… boilerplate code everywhere!

Each command button has its own associated actions implemented in its own set of procedures, and that creates a lot of noise and reduces the signal when we’re reading the code, and that’s a clear sign the abstraction level needs to go up a bit.

Abstraction Levels
Think of the steps involved in making a cup of coffee, in maybe 3-5 steps. Think of a descriptive verb for each step, then think of how each step could be broken down into another 3-5 steps, and then use descriptive names for these steps, too. The names at the top level are necessarily going to be more abstract than those in the lower level(s): that’s what abstraction levels refers to. Now imagine doing all that in one giant procedure scope and you can see the benefits of balancing abstraction and indirection in programming 🙂

Moving that boilerplate to Public procedures in standard modules would “work” to clean up the form module… but then it would also pretty much defeat the purpose of encapsulating things into objects… and then when (not if) one such procedure needs any state, then that state soon becomes global state, and that is absolutely not something we want to have to resort to.

Command & Conquer

Using the command pattern (even without MVVM command bindings), a CreateButton_Click handler would still be responsible for kicking the “create a new item” logic into action… but now that logic would be living in some ICommand implementation, encapsulating its dependencies and state (and thus moving these outside of the form’s code-behind but not into global scope now).

The MVVM infrastructure defines an ICommand interface that looks like this:

'@Folder MVVM.Infrastructure.Abstract
'@ModuleDescription "An object that represents an executable command."
'@Interface
'@Exposed
Option Explicit

'@Description "Returns True if the command is enabled given the provided binding context (ViewModel)."
Public Function CanExecute(ByVal Context As Object) As Boolean
End Function

'@Description "Executes the command given the provided binding context (ViewModel)."
Public Sub Execute(ByVal Context As Object)
End Sub

'@Description "Gets a user-friendly description of the command."
Public Property Get Description() As String
End Property

This makes a command as an abstraction that has:

  • A user-friendly description of what the command does.
  • A function that takes a context object and returns a Boolean value that indicates whether the command can currently be executed.
  • An Execute procedure that takes a context object and, well, executes the command.

The mysterious Context parameter is an object that encapsulates the state, the data we’re working with. In MVVM that would be the ViewModel instance.

MVVM command bindings use the Description property to set the ControlToolTip string of a binding’s target CommandButton object, and automatically invokes the CanExecute method as property bindings update, which automatically enables or disables the bound command button control: the command pattern works very, very well with Model-View-ViewModel, but nothing says we cannot use the command pattern without it.

So let’s strip the interface of its Description property, leaving only the CanExecute and Execute methods:

'@Folder CommandPattern.Example
'@ModuleDescription "An object that represents an executable command."
'@Interface
'@Exposed
Option Explicit

'@Description "Returns True if the command is enabled given the provided context."
Public Function CanExecute(ByVal Context As Object) As Boolean
End Function

'@Description "Executes the command given the provided context."
Public Sub Execute(ByVal Context As Object)
End Sub

We’re still going to need a Click handler in the code-behind for each CommandButton on a form, but now that we have an ICommand abstraction to code against, we can already go back to the Divide & Conquer form’s code-behind and watch it melt:

Private CreateNewItem As ICommand
Private DeletedSelectedItems As ICommand
Private EditSelectedItem As ICommand

Public Property Get Model() As Object
    'gets an object holding the data needed for this form
End Property

Private Sub CreateButton_Click()
    CreateNewItem.Execute Me.Model
End Sub

Private Sub DeleteButton_Click()
    DeleteSelectedItems.Execute Me.Model
End Sub

Private Sub EditButton_Click()
    EditSelectedItem.Execute Me.Model
End Sub

That of course is again just simplified illustrative code, but the lower-abstraction implementation details that were omitted for brevity in the “divide & conquer” code no longer need to find a place to call home, and no longer even need to be omitted either: that lower-abstraction code is simply gone from the code-behind now, and lives in a handful of distinct objects that implement the ICommand interface, such that the only thing a button’s Click handler needs to do now is to invoke a high-abstraction method that does whatever it needs to do.

At a glance, such a one-liner CreateNewItem.Execute instruction looks very similar to another one-liner CreateNewItem instruction (both involve a procedure call against an object – but only one of them is a command); the difference is that now the form is [blissfully] unaware of how that activity is going to happen, and a maintainer looking for the code that creates a new item will find it in a CreateNewItemCommand class, instead of somewhere in the middle of other specialized procedure scopes all in the same module.

Embracing Changes

Code changes, code evolves, it’s inevitable: code lives. When we code against abstractions, we reduce the code’s resistance to change. You want your code to embrace changes, you want it to welcome changes and extensions.

By coding against an ICommand interface, the only thing we commit to is that clicking a button will do something; we don’t know what and we don’t even need to care, and that’s what not resisting change means: we aren’t saying “run procedure X in module Y” anymore, we’re saying “run X implemented by any class whatsoever“. The actual code that runs the command is bound at run-time and doesn’t even need to exist for the code to compile, and the form is still fully-functional given no-op stub “commands” – we just need to get more abstract about what “to be functional” means for a form (meaning, if we click a button and ICommand.Execute is invoked, then we’re good – that’s all we need the form to do here).

The hypothetical example code above implies a separate CreateItemCommand class; it might look something like this:

Option Explicit
Implements ICommand

Private Function ICommand_CanExecute(ByVal Context As Object) As Boolean
    ICommand_CanExecute = True
End Function

Private Sub ICommand_Execute(ByVal Context As Object)
    With New ItemEditorForm
        .Show
        If .Cancelled Then Exit Sub
        AddToSource .Model, Context
    End With
End Sub

Private Sub AddToSource(ByVal Thing As Something, ByVal Context As Object)
    Context.AddThing Thing
End Sub

Note that this is again really just moving private methods from one place into their own class, so AddToSource would be the same code as before, only now the “source” collection that needs an item added to, would live in the Context object, which we’re accessing late-bound here for simplicity’s sake, but a command implementation that works with a particular specific type of Context object should validate that, and cast the parameter into a local variable declared with the appropriate type, so as to avoid such unnecessary late binding, like this:

Private Sub DoSomething(ByVal Context As Object)
    Debug.Assert TypeOf Context Is Class1
    Dim LocalContext As Class1
    Set LocalContext = Context '<~ type mismatch here if the assert fails
    'carry on using LocalContext with early-bound member calls
End Sub

By moving the implementation out of the button’s Click handler, we make it much easier to later repurpose that button, or to make a future button elsewhere that invokes the same command. The form module doesn’t need to know about any concrete implementation of the ICommand interface: a button can be wired-up to any command, swapping SomeCommand for a SomeOtherCommand implementation is all that’s needed.


One Step Further

We’ve seen how to pull functionality from a form’s code-behind and refactor it into specialized command objects that can be invoked from a button’s Click handler. The nicest thing about such commands, is that they are full-fledged objects, which means they can be passed around as parameters – and Model-View-ViewModel (MVVM) leverages that.

In the MVVM object model, you have a top-level AppContext object that exposes an ICommandManager object: this manager is responsible for holding a reference to all command bindings in your MVVM application, and there’s an IBindingManager that notifies it whenever a property binding updates in a way that may require commands’ CanExecute method to be evaluated.

When coding against the MVVM object model, you no longer wire-up event handlers: the MVVM infrastructure automatically does it for you – so the only code that remains (that actually does anything) in a form’s code-behind, is code that wires up form controls to property and command bindings – the rest is just implementations for IView and ICancellable interfaces (as applicable), and then a factory method can initialize a bunch of properties (or the properties can be Set from outside the module, but a Create factory method works very well with UserForm classes for property injection):

Option Explicit
Implements IView
Implements ICancellable

Private Type TState
    Context As MVVM.IAppContext
    ViewModel As ExampleViewModel '<~ any class implementing INotifyPropertyChanged
    IsCancelled As Boolean
    CreateNewItem As ICommand
    DeletedSelectedItems As ICommand
    EditSelectedItem As ICommand
End Type

Private This As TState

'...properties...

Public Property Get ViewModel() As ExampleViewModel
    Set ViewModel = This.ViewModel
End Property

Private Sub InitializeView()
    With This.Context.Commands
        .BindCommand ViewModel, Me.CreateButton, ViewModel.CreateNewItem
        .BindCommand ViewModel, Me.DeleteButton, ViewModel.DeleteSelectedItems
        .BindCommand ViewModel, Me.EditButton, ViewModel.EditSelectedItem
        .BindCommand ViewModel, Me.CancelButton, CancelCommand.Create(Me)
    End With
End Sub

'...interface implementations...

The UI controls are still referred to as Me.CreateButton, Me.DeleteButton, and Me.EditButton (added Me.CancelButton for good measure), but now instead of handling their Click event we bind them to ICommand objects – whose references we conveniently expose as Property Get members of our ViewModel, but we can also bind a command that we create inline, like this CancelCommand instance. Shame the QueryClose event isn’t exposed, because then binding a CancelCommand to a UserForm would be all you’d need to do for it to automagically properly close/cancel a dialog.

Note that the form doesn’t even need to know what specific ICommand implementations it’s given to work with, at all: here the form is coupled with the CancelCommand, but all other commands (create, delete, edit) are binding to public ICommand properties that live on the ViewModel object.

Full Circle: EventCommand (MVVM)

Not all commands are created equal: a command like CancelCommand is generic enough that it can work with any ICancellable object, and an AcceptCommand can work with any implementation of the IView interface. On the other hand, something feels wrong about systematically implementing any & all commands in their own classes.

Having each command neatly factored into its own class module is a great way to implement complex commands, but can be overkill when things are relatively trivial – very often the ViewModel class already has access to every object a command needs, and having a way to make the ViewModel itself implement the command would solve this.

I’m going to introduce an EventCommand class into the MVVM infrastructure code, to do exactly this:

'@Folder MVVM.Common.Commands
'@ModuleDescription "A command that allows the ViewModel to supply the implementation."
'@PredeclaredId
'@Exposed
Option Explicit
Implements ICommand

Private Type TState
    Description As String
End Type

Private This As TState

Public Event OnCanExecute(ByVal Context As Object, ByRef outResult As Boolean)
Public Event OnExecute(ByVal Context As Object)

'@Description "Creates a new instance of this ICommand class. Set the returned reference to a WithEvents variable."
Public Function Create(ByVal Description As String) As ICommand
    Dim Result As EventCommand
    Set Result = New EventCommand
    Result.Description = Description
    Set Create = Result
End Function

'@Description "Gets/sets the command's Description."
Public Property Get Description() As String
    Description = This.Description
End Property

Friend Property Let Description(ByVal RHS As String)
    This.Description = RHS
End Property

Private Function ICommand_CanExecute(ByVal Context As Object) As Boolean
    Dim outResult As Boolean
    outResult = True
    RaiseEvent OnCanExecute(Context, outResult)
    ICommand_CanExecute = outResult
End Function

Private Property Get ICommand_Description() As String
    ICommand_Description = This.Description
End Property

Private Sub ICommand_Execute(ByVal Context As Object)
    RaiseEvent OnExecute(Context)
End Sub

In VBA we can’t pass functions around like we can with delegates in C#, but events are a nice language feature we can still leverage for this purpose. Code like this could be in any ViewModel class:

Private WithEvents PseudoDelegateCommand As EventCommand

'...

Private Sub Class_Initialize()
    Set PseudoDelegateCommand = EventCommand.Create("Full circle!")
End Sub

'...

Private Sub PseudoDelegateCommand_OnCanExecute(ByVal Context As Object, outResult As Boolean)
'supply the ICommand.CanExecute implementation here.
'assign outResult to False to disable the command (it's True by default).
'in principle, the Context *is* the ViewModel instance, so this assertion should hold:
    Debug.Assert Me Is Context
'it also means the Context parameter should probably be ignored.
End Sub

Private Sub PseudoDelegateCommand_OnExecute(ByVal Context As Object)
'supply the ICommand.Execute implementation here.
'in principle, the Context *is* the ViewModel instance, so this assertion should hold:
    Debug.Assert Me Is Context
'it also means the Context parameter should probably be ignored.
'EventCommand is useful for commands that are specific to a particular ViewModel,
'and don't really need to have their implementation extracted into their own class.
End Sub

And now we’ve gone full circle and essentially moved the Click handlers out of the View …and into the ViewModel – except these aren’t Click handlers now, although they will run when a user clicks the associated button (mind-boggling, right?): we’re essentially looking at callbacks here, invoked from within the MVVM infrastructure in response to control events… and/or INotifyPropertyChanged notifications from the ViewModel.

From a testability standpoint, it’s important to understand the implications: if you intend to have your ViewModel under a thorough suite of unit tests, then an EventCommand becomes somewhat of a liability. The OnExecute handler (or OnCanExecute, for that matter) shouldn’t require dependencies that the ViewModel doesn’t already have, so that tests can property-inject stub dependencies. In other words, unless the ViewModel already depends on an abstraction to access, say, a database connection or the file system, then the handlers of an EventCommand in that class shouldn’t connect to a database or access the file system.


You’re in command

Whether it’s for a workbook with many simple (-ish) macros, or for a full-fledged MVP, MVC, or MVVM application, implementing the command pattern lets you move the code that contains your actual functionality wherever it makes the most sense to have it. Unless you’re writing a Smart UI, that place is pretty much never the code-behind of the View module. By implementing an ICommand interface directly, you can move all that code from the UI to a command class whose sole purpose is to provide that particular piece of functionality.

Using an EventCommand with MVVM, you can even move that code from the UI to literally anywhere you want, as long as that is a class module (only class modules can have a WithEvents instance variable). It’s not uncommon to see a ViewModel class include somewhat high-abstraction code that provides commands’ implementations.

See and follow github.com/rubberduck-vba/MVVM for the Model-View-ViewModel infrastructure code that makes command bindings a thing in VBA, as well as examples (including a Smart UI!) and additional documentation.

Builder Walkthrough

Note: this article was updated 2021-04-13 with screenshots from the latest v2.5.1.x pre-release build; the extract interface enhancements shown will green-release with v2.5.2.

We’ve seen how to leverage the default instance of a class module to define a stateless interface that’s perfect for a factory method. At the right abstraction level, most objects will not require more than just a few parameters. Often, parameters are related and can be abstracted/regrouped into their own object. Sometimes that makes things expressive enough. Other times, there’s just nothing we can do to work around the fact that we need to initialize a class with a dozen or more values.

The example code for this article can be found in our Examples repository.

A class with many properties

Such classes are actually pretty common; any entity object representing a database record would fit the bill. Let’s make a User class. We’re using Rubberduck, so this will be quick!

We start with a public field for each property we want:

Option Explicit
Public Id As String
Public UserName As String
Public FirstName As String
Public LastName As String
Public Email As String
Public EmailVerified As Boolean
Public TwoFactorEnabled As Boolean
Public PhoneNumber As String
Public PhoneNumberVerified As Boolean
Public AvatarUrl As String

Now we hit Ctrl+` to trigger a parse, right-click any of the variables and select Encapsulate Field from the Refactor menu (or Ctrl+Shift+F if you haven’t tweaked the default hotkeys):

The command will be disabled if the caret/selection isn’t on a public field, or if the module has been modified since the last time Rubberduck parsed it.

Check the wrap fields in private type box, then click the Select all button and hit OK.

The Encapsulate Field refactoring also lets you rename the properties and their respective backing field.

Now the module looks like this, and all you had to do was to declare a bunch of public fields:

Option Explicit
Private Type TUser
    Id As String
    UserName As String
    FirstName As String
    LastName As String
    Email As String
    EmailVerified As Boolean
    TwoFactorEnabled As Boolean
    PhoneNumber As String
    PhoneNumberVerified As Boolean
    AvatarUrl As String
End Type
Private this As TUser
Public Property Get Id() As String
    Id = this.Id
End Property
Public Property Let Id(ByVal value As String)
    this.Id = value
End Property
Public Property Get UserName() As String
    UserName = this.UserName
End Property
Public Property Let UserName(ByVal value As String)
    this.UserName = value
End Property
Public Property Get FirstName() As String
    FirstName = this.FirstName
End Property
Public Property Let FirstName(ByVal value As String)
    this.FirstName = value
End Property
Public Property Get LastName() As String
    LastName = this.LastName
End Property
Public Property Let LastName(ByVal value As String)
    this.LastName = value
End Property
Public Property Get Email() As String
    Email = this.Email
End Property
Public Property Let Email(ByVal value As String)
    this.Email = value
End Property
Public Property Get EmailVerified() As Boolean
    EmailVerified = this.EmailVerified
End Property
Public Property Let EmailVerified(ByVal value As Boolean)
    this.EmailVerified = value
End Property
Public Property Get TwoFactorEnabled() As Boolean
    TwoFactorEnabled = this.TwoFactorEnabled
End Property
Public Property Let TwoFactorEnabled(ByVal value As Boolean)
    this.TwoFactorEnabled = value
End Property
Public Property Get PhoneNumber() As String
    PhoneNumber = this.PhoneNumber
End Property
Public Property Let PhoneNumber(ByVal value As String)
    this.PhoneNumber = value
End Property
Public Property Get PhoneNumberVerified() As Boolean
    PhoneNumberVerified = this.PhoneNumberVerified
End Property
Public Property Let PhoneNumberVerified(ByVal value As Boolean)
    this.PhoneNumberVerified = value
End Property
Public Property Get AvatarUrl() As String
    AvatarUrl = this.AvatarUrl
End Property
Public Property Let AvatarUrl(ByVal value As String)
    this.AvatarUrl = value
End Property

I love this feature! Rubberduck has already re-parsed the module, so next we right-click anywhere in the module and select the Extract Interface refactoring, and check the box to select all Property Get accessors (skipping Property Let):

Extract Interface can automatically implement the extracted interface for you, and you can extract a public interface out of a private class.

Having a read-only interface for client code that doesn’t need the Property Let accessors makes an objectively cleaner API: assignments are recognized as invalid at compile time.

We get a read-only IUser interface for our efforts (!), and now the User class has an Implements IUser instruction at the top, …and these new members at the bottom:

Private Property Get IUser_ThingId() As String
    IUser_ThingId = ThingId
End Property

Private Property Get IUser_UserName() As String
    IUser_UserName = UserName
End Property

Private Property Get IUser_FirstName() As String
    IUser_FirstName = FirstName
End Property

Private Property Get IUser_LastName() As String
    IUser_LastName = LastName
End Property

Private Property Get IUser_Email() As String
    IUser_Email = Email
End Property

Private Property Get IUser_EmailVerified() As Boolean
    IUser_EmailVerified = EmailVerified
End Property

Private Property Get IUser_TwoFactorEnabled() As Boolean
    IUser_TwoFactorEnabled = TwoFactorEnabled
End Property

Private Property Get IUser_PhoneNumber() As String
    IUser_PhoneNumber = PhoneNumber
End Property

Private Property Get IUser_PhoneNumberVerified() As Boolean
    IUser_PhoneNumberVerified = PhoneNumberVerified
End Property

Private Property Get IUser_AvatarUrl() As String
    IUser_AvatarUrl = AvatarUrl
End Property

The scary part is that it feels as though if Extract Interface accounted for the presence of a Private Type in a similar way Encapsulate Field does, then even the TODO placeholder bits could be fully automated. Might be something to explore there… Update: automagic implementation completed!

Now we have our read-only interface worked out, if we go by previous posts’ teachings, , that is where we make our User class have a predeclared instance, and expose a factory method that I’d typically name Create:

'@Description "Creates and returns a new user instance with the specified property values."
Public Function Create(ByVal Id As String, ByVal UserName As String, ...) As IUser
    '...
End Function

Without Rubberduck, in order to have a predeclared instance of your class you would have to export+remove the class module, locate the exported .cls file, open it in Notepad++, edit the VB_PredeclaredId attribute value to True, save+close the file, then re-import it back into your VBA project.

With Rubberduck, there’s an annotation for that: simply add '@PredeclaredId at the top of the class module, parse, and there will be a result for the AttributeValueOutOfSync inspection informing you that the class’ VB_PredeclaredId attribute value disagrees with the @PredeclaredId annotation, and then you apply the quick-fix you want, and you just might have synchronized hidden attributes across the with a single click.

'@PredeclaredId
Option Explicit

When it’s a factory method for a service class that takes in dependencies, 2-3 parameters is great, 5+ is suspicious. But here we’re taking in values, pure data – not some IFileWriter or other abstraction. And we need quite a lot of them (here 10, but who knows how many that can be!), and that’s a problem, because this is very ugly:

Set identity = User.Create("01234", "Rubberduck", "contact@rubberduckvba.com", False, ...)

Using named parameters can help:

Set identity = User.Create( _
    Id:="01234", _
    UserName:="Rubberduck", _
    Email:="contact@rubberduckvba.com", _
    EmailVerified:=False, _
    Phone:="555-555-5555", _
    PhoneVerified:=False, _
    ...)

But the resulting code still feels pretty loaded, and that’s with consistent line breaks. Problem is, that limits the number of factory method parameters to 20-ish (if we’re nice and stick to one per line), since that’s how many line continuations the compiler will handle for a single logical line of code.

Surely there’s a better way.

Building the Builder

I wrote about this pattern in OOP Design Patterns: The Builder, but in retrospect that article was really just a quick overview. Let’s explore the builder pattern.

I like to design objects from the point of view of the code that will be consuming them. In this case what we want to end up with, is something like this:

Set identity = UserBuilder.Create("01234", "Rubberduck") _
    .WithEmail("contact@rubberduckvba.com", Verified:=False) _
    .WithPhone("555-555-5555", Verified:=False) _
    .Build

This solves a few problems that the factory method doesn’t:

  • Optional arguments become explicitly optional member calls; long argument lists are basically eliminated.
  • Say Id and UserName are required, i.e. a User object would be invalid without these values; the builder’s own Create factory method can take these required values as arguments, and that way any User instance that was built with a UserBuilder is guaranteed to at least have these values.
  • If we can provide a value for EmailVerified but not for Email, or for PhoneVerified but not for Phone, and neither are required… then with individual properties the best we can do is raise some validation error after the fact. With a UserBuilder, we can have WithEmail and WithPhone methods that take a Verified Boolean parameter along with the email/phone, and guarantee that if EmailVerified is supplied, then Email is supplied as well.

I like to start from abstractions, so let’s add a new class module – but don’t rename it just yet, otherwise Rubberduck will parse it right away. Instead, copy the IUser interface into the new Class1 module, select all, and Ctrl+H to replace “Property Get ” (with the trailing space) with “Function With” (without the trailing space). Still with the whole module selected, we replace “String” and “Boolean” with “IUserBuilder”. The result should look like this:

'@Interface
Option Explicit
Public Function WithId() As IUserBuilder
End Function
Public Function WithUserName() As IUserBuilder
End Function
Public Function WithFirstName() As IUserBuilder
End Function
Public Function WithLastName() As IUserBuilder
End Function
Public Function WithEmail() As IUserBuilder
End Function
Public Function WithEmailVerified() As IUserBuilder
End Function
Public Function WithTwoFactorEnabled() As IUserBuilder
End Function
Public Function WithPhoneNumber() As IUserBuilder
End Function
Public Function WithPhoneNumberVerified() As IUserBuilder
End Function
Public Function WithAvatarUrl() As IUserBuilder
End Function

We’re missing a Build method that returns the IUser we’re building:

Public Function Build() As IUser
End Function

Now we add the parameters and remove the members we don’t want, merge the related ones into single functions – this is where we define the shape of our builder API: if we want to make it hard to create a User with a LastName but without a FirstName, or one with TwoFactorEnabled and PhoneNumberVerified set to True but without a PhoneNumber value… then with a well-crafted builder interface we can make it do exactly that.

Once we’re done, we can rename the class module to IUserBuilder, and that should trigger a parse. The interface might look like this now:

'@Interface
'@ModuleDescription("Incrementally builds a User instance.")
Option Explicit
'@Description("Returns the current object.")
Public Function Build() As IUser
End Function
'@Description("Builds a user with a first and last name.")
Public Function WithName(ByVal FirstName As String, ByVal LastName As String) As IUserBuilder
End Function
'@Description("Builds a user with an email address.")
Public Function WithEmail(ByVal Email As String, Optional ByVal Verified As Boolean = False) As IUserBuilder
End Function
'@Description("Builds a user with SMS-based 2FA enabled.")
Public Function WithTwoFactorAuthentication(ByVal PhoneNumber As String, Optional ByVal Verified As Boolean = False) As IUserBuilder
End Function
'@Description("Builds a user with an avatar at the specified URL.")
Public Function WithAvatar(ByVal Url As String) As IUserBuilder
End Function

Then we can add another class module, and type Implements IUserBuilder under Option Explicit, then hit Ctrl+` to parse. Unless you disabled the “check if code compiles before parsing” setting (it’s enabled by default), you should be seeing this warning:

The project can’t compile, because the interface isn’t implemented.

Click Yes to parse anyway (normally we only want compilable code, but in this case we know what we’re doing, I promise), then right-click somewhere in the Implements IUserBuilder statement, and select the Implement Interface refactoring:

Creating all these method stubs manually, or… letting Rubberduck create them all at once in a split-second?

The result is as follows, and makes a good starting point:

Option Explicit
Implements IUserBuilder
Private Function IUserBuilder_Build() As IUser
    Err.Raise 5 'TODO implement interface member
End Function
Private Function IUserBuilder_WithName(ByVal FirstName As String, ByVal LastName As String) As IUserBuilder
    Err.Raise 5 'TODO implement interface member
End Function
Private Function IUserBuilder_WithEmail(ByVal Email As String, Optional ByVal Verified As Boolean = False) As IUserBuilder
    Err.Raise 5 'TODO implement interface member
End Function
Private Function IUserBuilder_WithTwoFactorAuthentication(ByVal PhoneNumber As String, Optional ByVal Verified As Boolean = False) As IUserBuilder
    Err.Raise 5 'TODO implement interface member
End Function
Private Function IUserBuilder_WithAvatar(ByVal Url As String) As IUserBuilder
    Err.Raise 5 'TODO implement interface member
End Function

We’re “building” an IUser object. So we have a module-level User object (we need the class’ default interface here, so that we can access the Property Let members), and each With method sets one property or more and then returns the current object (Me). That last part is critical, it’s what makes the builder methods chainable. We’ll need a Build method to return an encapsulated IUser object. So the next step will be to add a @PredeclaredId annotation and implement a Create factory method that takes the required values and injects the IUser object into the IUserBuilder instance we’re returning; then we can remove the members for these required values, leaving only builder methods for the optional ones. We will also add a value parameter of the correct type to each builder method, and make them all return the current object (Me). Once the class module looks like this, we can rename it to UserBuilder, and Rubberduck parses the code changes – note the @PredeclaredId annotation (needs to be synchronized to set the hidden VB_PredeclaredId attribute to True:

'@PredeclaredId
'@ModuleDescription("Builds a User object.")
Option Explicit
Implements IUserBuilder
Private internal As User
'@Description("Creates a new UserBuilder instance.")
Public Function Create(ByVal Id As String, ByVal UserName As String) As IUserBuilder
    Dim result As UserBuilder
    Set result = New UserBuilder
    
    '@Ignore UserMeaningfulName FIXME
    Dim obj As User
    Set obj = New User
    obj.Id = Id
    obj.UserName = UserName
    
    Set result.User = internal
    Set Create = result
End Function
'@Ignore WriteOnlyProperty
'@Description("For property injection of the internal IUser object; only the Create method should be invoking this member.")
Friend Property Set User(ByVal value As IUser)
    If Me Is UserBuilder Then Err.Raise 5, TypeName(Me), "Member call is illegal from default instance."
    If value Is Nothing Then Err.Raise 5, TypeName(Me), "'value' argument cannot be a null reference."
    Set internal = value
End Property
Private Function IUserBuilder_Build() As IUser
    If internal Is Nothing Then Err.Raise 91, TypeName(Me), "Builder initialization error: use UserBuilder.Create to create a UserBuilder."
    Set IUserBuilder_Build = internal
End Function
Private Function IUserBuilder_WithName(ByVal FirstName As String, ByVal LastName As String) As IUserBuilder
    internal.FirstName = FirstName
    internal.LastName = LastName
    Set IUserBuilder_WithName = Me
End Function
Private Function IUserBuilder_WithEmail(ByVal Email As String, Optional ByVal Verified As Boolean = False) As IUserBuilder
    internal.Email = Email
    internal.EmailVerified = Verified
    Set IUserBuilder_WithEmail = Me
End Function
Private Function IUserBuilder_WithTwoFactorAuthentication(ByVal PhoneNumber As String, Optional ByVal Verified As Boolean = False) As IUserBuilder
    internal.TwoFactorEnabled = True
    internal.PhoneNumber = PhoneNumber
    internal.PhoneNumberVerified = Verified
    Set IUserBuilder_WithTwoFactorAuthentication = Me
End Function
Private Function IUserBuilder_WithAvatar(ByVal Url As String) As IUserBuilder
    internal.AvatarUrl = Url
    Set IUserBuilder_WithAvatar = Me
End Function

Now, when I said default instances and factory methods (here too) are some kind of fundamental building block, I mean we’re going to be building on top of that, starting with this builder pattern; the Create method is intended to be invoked off the class’ default instance, like this:

Set builder = UserBuilder.Create(internalId, uniqueName)

The advantages are numerous, starting with the possibility to initialize the builder with everything it needs (all the required values), so that the client code can call Build and consume a valid User object right away.

Side note about this FIXME comment – there’s more to it than it being a signpost for the reader/maintainer:

    '@Ignore UserMeaningfulName FIXME
    Dim obj As User

By default only TODO, BUG, and NOTE markers are picked up, but you can easily configure Rubberduck to find any marker you like in comments, and then the ToDo Explorer lets you easily navigate them all:

Rubberduck has a ToDo Explorer toolwindow that can be configured (click the cogwheel icon) to pick up “FIXME” anywhere in comments, anywhere in the project. Or “HERE BE DRAGONS”.

Another noteworthy observation:

'@Ignore WriteOnlyProperty
'@Description("For property injection of the internal IUser object; only the Create method should be invoking this member.")
Friend Property Set User(ByVal value As IUser)
    If Me Is UserBuilder Then Err.Raise 5, TypeName(Me), "Member call is illegal from default instance."
    If value Is Nothing Then Err.Raise 5, TypeName(Me), "'value' argument cannot be a null reference."
    Set internal = value
End Property

Me is always the current object, as in, an instance of this class module, presenting the default interface of this class module: the If Me Is UserBuilder condition evaluates whether Me is the object known as UserBuilder – and right now there’s no such thing and the code doesn’t compile.

Synchronizing Attributes & Annotations

Rubberduck knows we mean that class to have a VB_PredeclaredId attribute value of True because of the @PredeclaredId annotation, but it’s still just a comment at this point. Bring up the inspection results toolwindow, and find the results for the MissingAttribute inspection under Rubberduck Opportunities:

Clicking Fix all occurrences in project will automatically add all the missing attributes.

That didn’t fix the VB_PredeclaredId attributes! Why?! The reason is that the attribute isn’t missing, only its value is out of sync. We’ll have to change this (pull requests welcome!), but for now you’ll find the AttributeValueOutOfSync inspection results under the Code Quality Issues group. If you group results by inspection, its miscategorization doesn’t matter though:

When attributes and annotations contradict each other, the AttributeValueOutOfSync inspection starts issuing results.

Adjust the attribute value accordingly (right-click the inspection result, or select “adjust attribute value(s)” from the “Fix” dropdown menu), and now your UserBuilder is ready to use:

Dim identity As IUser
Set identity = UserBuilder.Create(uniqueId, uniqueName) _
                          .WithName(first, last) _
                          .WithEmail(emailAddress) _
                          .Build

…and misuse:

Set UserBuilder.User = New User '<~ runtime error, illegal from default instance
Debug.Print UserBuilder.User.AvatarUrl '<~ compile error, invalid use of property
Set builder = New UserBuilder
Set identity = builder.Build '<~ runtime error 91, builder state was not initialized
Set builder = New UserBuilder
Set builder = builder.WithEmail(emailAddress) '<~ runtime error 91

Conclusions

Model classes with many properties are annoying to write, and annoying to initialize. Sometimes properties are required, other times properties are optional, others are only valid if another property has such or such value. This article has shown how effortlessly such classes can be created with Rubberduck, and how temporal coupling and other state issues can be solved using the builder creational pattern.

Using this pattern as a building block in the same toolbox as factory methods and other creational patterns previously discussed, we can now craft lovely fluent APIs that can chain optional member calls to build complex objects with many properties without needing to take a gazillion parameters anywhere.

Secure ADODB

Unless you’re hosted in Access, your VBA project doesn’t have access to a database engine. If you’re in Excel, it’s easy to treat the host workbook as a database and each worksheet as a table. While we can build an application that uses Excel worksheets to store data, we probably shouldn’t do that. The reasons are many, but primarily (pun …yeah, intended), we want to be able to establish bullet-proof referential integrity between records/tables; while Excel is great for many things, it’s useless for that: it’s the job of a relational database system (RDBMS), not that of any worksheet software, no matter how powerful. Power Query is very much worth looking into, but if you’re building a small CRUD (Create/Read/Update/Delete) application in VBA, you’ll want VBA code responsible for the data access – enter ADODB, …and every pitfall that comes with it.

In this article we will explore a heavily object-oriented solution to querying a database securely with the ADODB library.


Securely?

Querying a database with ADODB is easy: just set up a connection, open it, then execute whatever SQL statement you need through the Connection, and you get the results in a Recordset object:

Dim conn As ADODB.Connection
Set conn = New ADODB.Connection
conn.Open "ConnectionString"

Dim rs As ADODB.Recordset
Set rs = conn.Execute("SELECT Field1, Field2 FROM Table1")

'...

rs.Close
conn.Close

That is great for one-timer, ad-hoc queries: things quickly get messy when you start needing multiple queries, or when your SQL statement needs to be invoked repeatedly with different values:

Dim conn As ADODB.Connection
Set conn = New ADODB.Connection
conn.Open "ConnectionString"

Dim i As Long
For i = 1 To 10
    Dim rs As ADODB.Recordset
    Set rs = conn.Execute("SELECT Field1, Field2 FROM Table1 WHERE Field3 = " & i)
    '...
    rs.Close
Next
conn.Close

This right here – WHERE SomeField = " & i, is making the database engine work harder than it needs to… and it’s costing server-side performance, because as far as the engine knows, it’s getting a different query every time – and thus computes the same execution plan over and over, every time… when it could just be reusing it. Databases are smart. Like, wicked smart… but yeah we still need to ask for the right thing!

Compare to something like this:

Const sql As String = "SELECT Field1, Field2 FROM Table1 WHERE Field3 = ?"
Dim conn As ADODB.Connection
Set conn = New ADODB.Connection
conn.Open "ConnectionString"

Dim i As Long
For i = 1 To 10
    Dim cmd As ADODB.Command
    Set cmd = New ADODB.Command
    cmd.CommandType = adCmdText
    cmd.CommandText = sql
    cmd.Parameters.Append cmd.CreateParameter(Type:=adInteger, Value:= i)

    Dim rs As ADODB.Recordset
    Set rs = cmd.Execute
    '...
    rs.Close
Next
conn.Close

Oh my, so much more code, so little gain – right?

Using ADODB.Command when queries involve a WHERE (and/or VALUES) clause and user-provided (directly or not) values is not only more efficient (the cached execution plan is reused because the command string is identical every time), it’s also more secure. Concatenating user inputs into SQL command strings is a common rookie mistake, and it’s a practice that is way more widespread than it should be (regardless of the language, paradigm, or platform); your code becomes vulnerable to SQL Injection Attacks – something that may or may not be in your threat model, but that inevitably turns into… easily avoidable bugs: think of what might happen if a user entered O'Connor in that LastName field. If you’re thinking “oh that’s easy! I’ll just double-up single quotes, and fixed!“, then you’re playing a needlessly exhausting game of cat-and-mouse with the next thing that will break your clever escaping: the mouse wins.

Abstract thoughts

Much simpler to just use an ADODB.Command every time, and when you need it parameterized, to Append any number of ADODB.Parameter objects to its Parameters collection. Except, it does make a lot of code to write, every time.

What do we do when we see repetitive patterns in code? If you’re thinking “we put it in a function!” then you’re thinking abstraction and that’s exactly the right train of thought.

We’re just going to take this abstraction… and make it an object. Then think of what objects it needs in order to do its job, and abstract these objects behind interfaces too, and take these abstractions in as constructor parameters of our Create “static” factory method. Rinse & repeat until all dependencies are property-injected and all responsibilities are nicely encapsulated into their own classes. It was fun!

I wrote an original version of this functionality little while ago – you can find the original version on Code Review, and see how different/similar it is to this simplified/improved version in our Examples repository on GitHub.

The original was just an ADODB wrapper class though, couldn’t really be unit-tested, and was annoying to maintain because it felt very repetitive. This version is separating the type mappings from the parameter-providing logic, which makes configuring these mappings is done through an object that’s solely responsible for these mappings; it also separates the command from the connection, and abstracts away that connection enough to enable unit testing and cover quite a large part of the API – but most importantly, this version exposes adequate abstractions for the calling code to use and stub in its own unit tests.

VBA code written with this API (and the principles it demonstrates) can easily be fully testable, without ever actually hitting any database.

I can do this in the immediate pane:

?UnitOfWork.FromConnectionString("connection string").Command.GetSingleValue("SELECT Field1 FROM Table1 WHERE Id=?", 1)

I mean, it’s a contrived example, but with a valid connection string, query, and arguments, that’s all we need to get an actual parameterized ADODB command sending that 1 as an actual ADODB parameter, …and the following debug output:

Begin connect...
Connect completed. Status: 1
Begin transaction completed. 
Begin execute...
Execute completed, -1 record(s) affected.
{whatever value was in Field1}
Rollback transaction completed.
Disconnect completed. Status: 1

I made DbConnection listen in on whatever events the ADODB connection is firing, pending the implementation of an adapter to expose some IDbConnectionEvents members – the idea is to end up with client code that can inject its own callbacks and do things like log such messages. In the meantime Debug.Print statements are producing this debug output, but that’s it’s an implementation detail: it doesn’t publicly expose any of these events. It couldn’t, either: the rest of the code needs to work with the IDbConnection interface, and interfaces unfortunately can’t expose events in VBA.


SecureADODB

Some might call it layered spaghetti. Others call it lasagna. I call it well-abstracted code that reads and maintains like a charm and provably works as intended. There is nothing, absolutely nothing wrong with having many class modules in a VBA project: the only problem is… well, the VBE itself:

Project Explorer is making OOP rather painful. In fact it makes any kind of modularization painful.
Code Explorer makes the VBE more OOP-friendly: now you can have folders regrouping modules by functionality rather than just by module type.

Nice, rich APIs involve many related objects, interfaces, methods – members that make up the object model the API’s client code will be working with. As long as we can keep all these classes organized, there’s no problem having many of them.

Before we look at the implementation, let’s review the interfaces and the overall structure.

Only two interfaces aren’t being stubbed for unit tests. IUnitOfWork because as the top-level object nothing in the object model consumes it. It is needed though, because client code can inject it as a dependency of some FooRepository class, and then tests can provide it with a StubUnitOfWork that implements IUnitOfWork.

The other “façade” interface is ITypeMap. This one isn’t really needed (neither is the predeclared instance of AdoTypeMappings or its Default factory method), something felt wrong with the client code without it. While the class is essentially just a dictionary / literally a map, there’s something rather elegant about depending on an ITypeMap rather than some Scripting.Dictionary.

The two dark blue interfaces are abstract factory interfaces, each with a “real” and a “stub” implementation for tests: these are very simple classes whose entire purpose is to create an object of a particular type.

If we consider IParameterProvider an implementation detail of IDbCommandBase, that leaves us with only the core stuff: IDbCommandBase, IDbCommand, and IDbConnection – everything else just revolves around these.

DbCommandBase

The old SqlCommand code had two sets of commands: “Execute” for methods you could pass a Connection to, and “QuickExecute” for methods that created a connection on-the-spot. I decided to split the two behaviors into two distinct implementation of the same interface, and that’s how I ended up with DefaultDbCommand and AutoDbCommand. As I was cleaning up the two new classes, I had to notice these two classes needed a number of common bits of functionality… as would any other implementation of IDbCommand.

In a language that supports inheritance, I would probably make the two classes inherit a third abstract “base” class where I’d implement the IDbCommand interface. In VBA, we can’t derive a class from another, or inherit members from another class: inheritance is flat-out unavailable. There’s an alternative though, and it’s arguably even better than inheritance: composition. We can put the common functionality in a third class, and then have the two implementations take an instance of that “base” class as we would any other dependency – effectively achieving what we wanted out of inheritance, but through composition.

Code is said to be “decoupled” when none of its concrete components are inter-dependent, as is apparent with the solid black “depends on” arrows here. Decoupled components can easily be swapped for other implementations, like …test stubs.

What’s wrong with inheritance?

Don’t get me wrong, inheritance is very cool: with an abstract class you can have templated methods, where a method in the base class (typically a method that implements some interface member) invokes an abstract or virtual method (typically with protected scope) that the inherited class must override and provide an implementation for. Rubberduck uses this pattern in quite a few places (inspections, notably). Without inheritance, it’s just not something that’s possible.

Inheritance is described as a “is a” relationship, while composition is more of a “has a” relationship. This is important, because when the only consideration weighting in favor of inheritance is the need for two classes to share some functionality, it’s exactly why inheritance should not be used.


Decoupling FTW

The “base” class appeared as a need to have a place for IDbCommand implementations to access shared functionality. I wanted to return disconnected recordsets, and retrieving the value of the first field of the first record of a recordset isn’t something that’s glaringly implementation-specific. The other piece of functionality I needed, was a function that creates the ADODB.Command object and adds the parameters.

Because I wanted this class to create the ADODB.Command, I needed it to be able to turn a Variant into an ADODB.Parameter through some mapping, and since I didn’t want my class to be necessarily coupled with that mapping, or anything remotely related to configuring ADODB parameters… I’m property-injecting an IParameterProvider dependency:

Public Function Create(ByVal provider As IParameterProvider) As IDbCommandBase
    Errors.GuardNonDefaultInstance Me, DbCommandBase
    Errors.GuardNullReference provider
    
    Dim result As DbCommandBase
    Set result = New DbCommandBase
    Set result.ParameterProvider = provider
    
    Set Create = result

End Function

Validating the command string / arguments

Since the commands are given an SQL command string to execute, and a ParamArray array of arguments that should have the same number of items as there are ? ordinal parameters in the SQL command string, we have an opportunity to catch a missing or extraneous argument before we even send the command string to the database server. And because this validation logic would have to be the same regardless of what IDbCommand implementation we’re looking at, DbCommandBase makes the best place to put it.

This implementation is probably too naive for a number of edge cases, but sufficient for most: we’re simply counting the number of ? characters in the sql string, and comparing that with the number of elements in the args array. We need to handle errors here, because if the args array is empty, evaluating UBound(args) and/or LBound(args) will throw a “subscript out of range” run-time error 9.

Public Function ValidateOrdinalArguments(ByVal sql As String, ByRef args() As Variant) As Boolean
    On Error GoTo CleanFail
    Dim result As Boolean
    
    Dim expected As Long
    expected = Len(sql) - Len(Replace(sql, "?", vbNullString))
    
    Dim actual As Long
    On Error GoTo CleanFail 'if there are no args, LBound/UBound are both out of bounds
    actual = UBound(args) + (1 - LBound(args))
    
CleanExit:
    result = (expected = actual)
    ValidateOrdinalArguments = result
    Exit Function
CleanFail:
    actual = 0
    Resume CleanExit
End Function

Getting a disconnected Recordset

If we created a database connection, issued a command against it, and received the recordset from ADODB.Command.Execute, and then we close the connection and return that recordset, then the calling code can’t use the data anymore: a connected recordset only works if the calling code owns the connection. So we need a way to issue a disconnected recordset, while still using an ADODB.Command. The way to do this, is to pass the command as the Source argument to Recordset.Open, and to use a static, client-side cursor:

Private Function GetDisconnectedRecordset(ByVal cmd As ADODB.Command) As ADODB.Recordset
    Errors.GuardNullReference cmd
    Errors.GuardNullReference cmd.ActiveConnection
    
    Dim result As ADODB.Recordset
    Set result = New ADODB.Recordset
    
    result.CursorLocation = adUseClient
    result.Open Source:=cmd, CursorType:=adOpenStatic
    
    Set result.ActiveConnection = Nothing
    Set GetDisconnectedRecordset = result
End Function

Getting a single value result

With functions to validate the parameters, create commands and get a disconnected recordset, we have everything we need for IDbCommand implementations to do their job, but if we leave it like this, we’ll end up with all implementations copying the logic of IDbCommand.GetSingleValue: best have that logic in DbCommandBase and avoid as much repetition as possible.

Private Function GetSingleValue(ByVal db As IDbConnection, ByVal sql As String, ByRef args() As Variant) As Variant
    Errors.GuardEmptyString sql
    
    Dim cmd As ADODB.Command
    Set cmd = CreateCommand(db, adCmdText, sql, args)
    
    Dim results As ADODB.Recordset
    Set results = GetDisconnectedRecordset(cmd)
    
    GetSingleValue = results.Fields.Item(0).value
End Function

Creating the command

A few things can go wrong when creating the ADODB.Command object: we need an ADODB.Connection that’s open, and the parameters must be valid. Since we’re not executing the command just yet, we don’t have to worry about everything that could go wrong actually executing the command string and processing the parameters on the server. So the strategy here is to guard against invalid inputs as much as possible, and then to handle errors when we add the parameters, and return the Command object with whatever parameters were successfully added. We don’t need to try salvaging the rest of the parameters if one blows up, since that failing parameter will fail command execution anyway, but there isn’t much we can do about it, other than perhaps throw an error and have the caller not even try to run the command – but here I decided that the server-side errors would be more useful than any custom “invalid parameter” error.

Note that the ADODB.Command object is actually created by the method-injected IDbConnection dependency. This creates a seam between the class and ADODB, despite the inherent coupling with the ADODB.Command type: it makes the command’s ActiveConnection an implementation detail of IDbConnection.CreateCommand, and that’s all I needed to make this method work with a stub connection that isn’t actually connecting to anything:

Private Function CreateCommand(ByVal db As IDbConnection, ByVal commandType As ADODB.CommandTypeEnum, ByVal sql As String, ByRef args() As Variant) As ADODB.Command
    Errors.GuardNullReference db
    Errors.GuardEmptyString sql
    Errors.GuardExpression db.State <> adStateOpen, message:="Connection is not open."
    Errors.GuardExpression Not ValidateOrdinalArguments(sql, args), message:="Arguments supplied are inconsistent with the provided command string parameters."
    
    Dim cmd As ADODB.Command
    Set cmd = db.CreateCommand(commandType, sql)
    
    On Error GoTo CleanFail
    Dim arg As ADODB.Parameter
    For Each arg In this.ParameterProvider.FromValues(args)
        cmd.parameters.Append arg
    Next
    
CleanExit:
    Set CreateCommand = cmd
    Exit Function
CleanFail:
    Resume CleanExit
End Function

DbCommand

As mentioned before, there are two implementations for the IDbCommand interface: one that creates and owns its own IDbConnection, the other that takes it in as a dependency.

This abstraction represents an object that can take an SQL statement and parameters, and return the result(s) to its caller.

DefaultDbCommand receives its IDbConnection dependency through property injection in its Create factory method.

AutoDbCommand takes a connection string and an IDbConnectionFactory instead.

UnitOfWork uses a DefaultDbCommand because the unit of work needs to own the connection, but AutoDbCommand could be used instead of a unit of work, if we just need a quick SELECT and no transaction.

Abstract Factory

IDbConnectionFactory is an Abstract Factory here. This is needed, because unit tests need to be able to inject a stub factory that produces stub connections: an abstract factory is a factory interface that creates objects of a type that is also an abstraction – in this case, IDbConnectionFactory.Create returns an IDbConnection object. Implementing this factory class is exactly as simple as you’d think – here’s DbConnectionFactory:

'@Exposed
'@Folder("SecureADODB.DbConnection")
'@ModuleDescription("An implementation of an abstract factory that creates DbConnection objects.")
Option Explicit
Implements IDbConnectionFactory

Private Function IDbConnectionFactory_Create(ByVal connString As String) As IDbConnection
    Set IDbConnectionFactory_Create = DbConnection.Create(connString)
End Function

And here’s StubDbConnectionFactory:

'@Folder("Tests.Stubs")
'@ModuleDescription("A stub acting as a IDbConnectionFactory implementation.")
Option Explicit
Implements IDbConnectionFactory
Private Type TInvokeState
    CreateConnectionInvokes As Long
End Type
Private this As TInvokeState

Private Function IDbConnectionFactory_Create(ByVal connString As String) As IDbConnection
    this.CreateConnectionInvokes = this.CreateConnectionInvokes + 1
    Set IDbConnectionFactory_Create = New StubDbConnection
End Function

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

The test stub is more “complex” because it tracks method invocations, so that tests can know whether & how many times any given member was invoked during a test run.

The Abstract Factory pattern is very useful with Dependency Injection: it gives us an abstraction to inject when a class needs a dependency that just cannot be injected when the object is created – the alternative would be tight coupling: if we weren’t injecting a connection factory, then the command class would’ve had to be the one invoking DbConnection.Create – tightly coupling it with the DbConnection class and instantly making unit testing impossible. An abstract factory removes the coupling and allows unit tests to inject an alternative/stub implementation of the factory that creates StubDbConnection objects.

Wrapping it all up

AutoDbConnection can very well be consumed as-is by the client code:

Dim results As ADODB.Recordset
Set results = AutoDbConnection.Create(connString, New DbConnectionFactory, DbCommandBase.Create(AdoParameterProvider.Create(AdoTypeMappings.Default))).Execute(sql)

The only problem is that, well, the dependencies need to be resolved somehow, and that means the client code is now responsible for wiring everything up. While each component has a clear purpose, explicitly creating all these objects quickly gets old and redundant: we need an object that simplifies this – enter IUnitOfWork, and now we can use this much simpler code:

Dim results As ADODB.Recordset
Set results = UnitOfWork.FromConnectionString(connString).Command.Execute(sql)

Unit of Work is a design pattern that encapsulates a transaction: each individual operation can succeed or fail, and the unit of work either succeeds or fails as a whole. These notions are abstracted in the IUnitOfWork interface:

'@Folder("SecureADODB.UnitOfWork")
'@ModuleDescription("Represents an object encapsulating a database transaction.")
'@Interface
'@Exposed
Option Explicit

'@Description("Commits the transaction.")
Public Sub Commit()
End Sub

'@Description("Rolls back the transaction.")
Public Sub Rollback()
End Sub

'@Description("Creates a new command to execute as part of the transaction.")
Public Function Command() As IDbCommand
End Function

When a UnitOfWork is created, it initiates a database transaction. When it is destroyed before the transaction is committed, the transaction gets rolled back and from the database’s point of view, it’s like nothing happened.

Transaction?

If you’re unfamiliar with database transactions, there’s an easy example to illustrate what they do: imagine you have an Accounts table, and you’re processing a transfer – you need to UPDATE the record for the source account to deduct the transfer amount, then UPDATE the record for the destination account to add the transferred amount. In a happy world where everything goes well that would be the end of it… but the world is a cruel place, and assuming the 1st command goes through, nothing guarantees nothing will blow up when sending the 2nd command. Without transactions, the funds would simply vanish: they’re gone from the first account, and they were never added to the second account. With a transaction, we can rollback everything when the 2nd operation completes, no funds vanish and the data is exactly the way it was before the transaction started.


Again, the implementation is pretty straightforward – the only peculiarity is that the class has two factory methods – one named Create that takes all the dependencies in, and another named FromConnectionString that conveniently wires up a default set of dependencies (and then passes them to the Create method to avoid duplicating code).

'@Folder("SecureADODB.UnitOfWork")
'@ModuleDescription("An object that encapsulates a database transaction.")
'@PredeclaredId
'@Exposed
Option Explicit
Implements IUnitOfWork
Private Type TUnitOfWork
    Committed As Boolean
    RolledBack As Boolean
    Connection As IDbConnection
    CommandFactory As IDbCommandFactory
End Type
Private this As TUnitOfWork

'@Description("Creates a new unit of work using default configurations.")
'@Ignore ProcedureNotUsed
Public Function FromConnectionString(ByVal connString As String) As IUnitOfWork
    
    Dim db As IDbConnection
    Set db = DbConnection.Create(connString)
    
    Dim provider As IParameterProvider
    Set provider = AdoParameterProvider.Create(AdoTypeMappings.Default)
    
    Dim baseCommand As IDbCommandBase
    Set baseCommand = DbCommandBase.Create(provider)
    
    Dim factory As IDbCommandFactory
    Set factory = DefaultDbCommandFactory.Create(baseCommand)
    
    Set FromConnectionString = UnitOfWork.Create(db, factory)
    
End Function

'@Inject: just an idea.. see #https://github.com/rubberduck-vba/Rubberduck/issues/5463
Public Function Create(ByVal db As IDbConnection, ByVal factory As IDbCommandFactory) As IUnitOfWork
    Errors.GuardNonDefaultInstance Me, UnitOfWork
    Errors.GuardNullReference factory
    Errors.GuardNullReference db
    Errors.GuardExpression db.State <> adStateOpen, message:="Connection should be open."
    
    Dim result As UnitOfWork
    Set result = New UnitOfWork
    Set result.CommandFactory = factory
    Set result.Connection = db
    
    Set Create = result
End Function

'@Inject: this member should only be invoked by Me.Create, where Me is the class' default/predeclared instance.
'@Ignore ProcedureNotUsed: false positive with v2.5.0.5418
Friend Property Set Connection(ByVal value As IDbConnection)
    Errors.GuardDoubleInitialization this.Connection
    Errors.GuardNullReference value
    Set this.Connection = value
    this.Connection.BeginTransaction
End Property

'@Inject: this member should only be invoked by Me.Create, where Me is the class' default/predeclared instance.
'@Ignore ProcedureNotUsed: false positive with v2.5.0.5418
Friend Property Set CommandFactory(ByVal value As IDbCommandFactory)
    Errors.GuardDoubleInitialization this.CommandFactory
    Errors.GuardNullReference value
    Set this.CommandFactory = value
End Property

Private Sub Class_Terminate()
    On Error Resume Next
    If Not this.Committed Then this.Connection.RollbackTransaction
    On Error GoTo 0
End Sub

Private Sub IUnitOfWork_Commit()
    Errors.GuardExpression this.Committed, message:="Transaction is already committed."
    Errors.GuardExpression this.RolledBack, message:="Transaction was rolled back."
    On Error Resume Next ' not all providers support transactions
    this.Connection.CommitTransaction
    this.Committed = True
    On Error GoTo 0
End Sub

Private Function IUnitOfWork_Command() As IDbCommand
    Set IUnitOfWork_Command = this.CommandFactory.Create(this.Connection)
End Function

Private Sub IUnitOfWork_Rollback()
    Errors.GuardExpression this.Committed, message:="Transaction is already committed."
    On Error Resume Next ' not all providers support transactions
    this.Connection.RollbackTransaction
    this.RolledBack = True
    On Error GoTo 0
End Sub

Errors

If you paid close attention to the code listings so far, you likely already noticed the many Errors.GuardXxxxx member calls scattered throughout the code. There are probably as many ways to deal with custom errors as there are VBA classes out there, this is one way. Probably not the best way, but it feels “just right” for me in this case and I think I like it enough to keep using it until the problems it creates become clearer (there’s always something). Errors is a standard private module in the project, that defines custom error codes. Okay I was lazy and deemed SecureADODBCustomError all I needed, but it could also have been an Enum with descriptive names for each custom error code.

The module simply exposes a small number of very simple Sub procedures that make it easy for the rest of the code to raise meaningful custom errors:

'@Folder("SecureADODB")
'@ModuleDescription("Global procedures for throwing common errors.")
Option Explicit
Option Private Module

Public Const SecureADODBCustomError As Long = vbObjectError Or 32

'@Description("Re-raises the current error, if there is one.")
Public Sub RethrowOnError()
    With VBA.Information.Err
        If .Number <> 0 Then
            Debug.Print "Error " & .Number, .Description
            .Raise .Number
        End If
    End With
End Sub

'@Description("Raises a run-time error if the specified Boolean expression is True.")
Public Sub GuardExpression(ByVal throw As Boolean, _
Optional ByVal Source As String = "SecureADODB.Errors", _
Optional ByVal message As String = "Invalid procedure call or argument.")
    If throw Then VBA.Information.Err.Raise SecureADODBCustomError, Source, message
End Sub

'@Description("Raises a run-time error if the specified instance isn't the default instance.")
Public Sub GuardNonDefaultInstance(ByVal instance As Object, ByVal defaultInstance As Object, _
Optional ByVal Source As String = "SecureADODB.Errors", _
Optional ByVal message As String = "Method should be invoked from the default/predeclared instance of this class.")
    Debug.Assert TypeName(instance) = TypeName(defaultInstance)
    GuardExpression Not instance Is defaultInstance, Source, message
End Sub

'@Description("Raises a run-time error if the specified object reference is already set.")
Public Sub GuardDoubleInitialization(ByVal instance As Object, _
Optional ByVal Source As String = "SecureADODB.Errors", _
Optional ByVal message As String = "Object is already initialized.")
    GuardExpression Not instance Is Nothing, Source, message
End Sub

'@Description("Raises a run-time error if the specified object reference is Nothing.")
Public Sub GuardNullReference(ByVal instance As Object, _
Optional ByVal Source As String = "SecureADODB.Errors", _
Optional ByVal message As String = "Object reference cannot be Nothing.")
    GuardExpression instance Is Nothing, Source, message
End Sub

'@Description("Raises a run-time error if the specified string is empty.")
Public Sub GuardEmptyString(ByVal value As String, _
Optional ByVal Source As String = "SecureADODB.Errors", _
Optional ByVal message As String = "String cannot be empty.")
    GuardExpression value = vbNullString, Source, message
End Sub

Most of these procedures are invoked as the first executable statement in a given scope, to raise an error given invalid parameters or internal state, such as these:

Private Sub IUnitOfWork_Commit()
    Errors.GuardExpression this.Committed, message:="Transaction is already committed."
    Errors.GuardExpression this.RolledBack, message:="Transaction was rolled back."
    On Error Resume Next ' not all providers support transactions
    this.Connection.CommitTransaction
    this.Committed = True
    On Error GoTo 0
End Sub

Consistently raising such errors is the single best way to ensure our objects are always in a known and usable state, because we outright forbid them to be invalid. These validation clauses are called guard clauses, hence the GuardXxxxx procedure names.

A lot of the unit tests simply verify that, given the specified conditions, the expected error is raised:

'@TestMethod("Factory Guard")
Private Sub Create_ThrowsIfNotInvokedFromDefaultInstance()
    On Error GoTo TestFail
    
    With New AutoDbCommand
        On Error GoTo CleanFail
        Dim sut As IDbCommand
        Set sut = .Create("connection string", New StubDbConnectionFactory, New StubDbCommandBase)
        On Error GoTo 0
    End With
    
CleanFail:
    If Err.Number = ExpectedError Then Exit Sub
TestFail:
    Assert.Fail "Expected error was not raised."
End Sub

If each guard clause has a unit test, then the tests are effectively documenting how the objects are meant to be used. With more specific custom errors, the tests would be more accurate, but there’s a point where you need to look at what you’ve got and say “I think I can work with that”, and move on.


Audience

Obviously, one doesn’t import 20 classes into their VBA project just to send one ADODB command to a database server. However if you’re maintaining a VB6 application that uses ADODB all over the place, leaks connections, leaves recordsets dangling, …then importing this API can really help tighten up the data access code in that legacy app. Or maybe you’re writing a complex data-driven system in VBA for Excel because that’s all you’ve got, and a UnitOfWork abstraction makes sense for you.

The goal here is mostly to 1) demonstrate proper usage of ADODB.Command for secure, parameterized queries, and 2) demonstrate that Classic VB (VB6/VBA) has always had everything everyone ever needed to write full-blown object-oriented code that leverages abstraction, encapsulation, and polymorphism – making it possible to write clean and fully unit-tested code.

…and of course, it makes a great practical application of the OOP concepts discussed in many other articles on this blog. Studying the code in this project gives you insight on…

  • OOP foundations: abstraction, encapsulation, polymorphism.
  • SOLID principles: single responsibility, dependency inversion, etc.
  • DI techniques: property injection, abstract factory.
  • Unit testing: what to test, how to test, stubbing dependencies, etc.
  • Using custom errors, guard clauses, input validation.
  • Leveraging Rubberduck annotations, minimizing inspection results.

Pattern: TryParse

Error-handling in VBA can easily get hairy. The best error handling code is no error handling code at all, and by writing our code at a high enough abstraction level, we can achieve exactly that – and leave the gory details in small, specialized, lower-abstraction procedures.

I’m growing rather fond of adapting the famous TryParse Pattern to VBA code, borrowed from the .NET landscape. Not really for performance reasons (VBA doesn’t deal with exceptions or stack traces), but for the net readability and abstraction gains. The crux of it is, you write a small, specialized function that returns a Boolean and takes a ByRef parameter for the return value – like this:

Public Function TryDoSomething(ByVal arg As String, ByRef outResult As Object) As Boolean
    'only return True and set outResult to a valid reference if successful
End Function

Let the calling code decide what to do with a failure – don’t pop a MsgBox in such a function: it’s the caller’s responsibility to know what to do when you return False.

The pattern comes from methods like bool Int32.TryParse(string, out Int32) in .NET, where an exception-throwing Int32 Int32.Parse(string) equivalent method is also provided: whenever there’s a TryDoSomething method, there’s an equivalent DoSomething method that is more straightforward, but also more risky.

Applied consistently, the Try prefix tells us that the last argument is a ByRef parameter that means to hold the return value; the out prefix is Apps Hungarian (the actual original intent of “[Systems] Hungarian Notation”) that the calling code can see with IntelliSense, screaming “this argument is your result, and must be passed by reference” – even though IntelliSense isn’t showing the ByRef modifier:

This pattern is especially useful to simplify error handling and replace it with standard flow control, like If statements. For example you could have a TryFind function that takes a Range object along with something to find in that range, invokes Range.Find, and only returns True if the result isn’t Nothing:

Dim result As Range
If Not TryFind(Sheet1.Range("A:A"), "test", result) Then
    MsgBox "Range.Find yielded no results.", vbInformation
    Exit Sub
End If

result.Activate 'result is guaranteed to be usable here

It’s especially useful for things that can raise a run-time error you have no control over – like opening a workbook off a user-provided String input, opening an ADODB database connection, or anything else that might fail for any reason well out of your control, and all your code needs to know is whether it worked or not.

Public Function TryOpenConnection(ByVal connString As String, ByRef outConnection As ADODB.Connection) As Boolean
    Dim result As ADODB.Connection
    Set result = New ADODB.Connection

    On Error GoTo CleanFail
    result.Open connString

    If result.State = adOpen Then
        TryOpenConnection = True
        Set outConnection = result
    End If

CleanExit:
    Exit Function

CleanFail:
    Debug.Print "TryOpenConnection failed with error: " & Err.Description
    Set result = Nothing
    'Resume CleanExit
    'Resume
End Function

The function returns True if the connection was successfully opened, False otherwise – regardless of whether that’s because the connection string is malformed, the server wasn’t found, or the connection timed out. If the calling code only needs to care about whether or not the connection succeeded, it’s perfect:

Dim adoConnection As ADODB.Connection
If Not TryOpenConnection(connString, adoConnection) Then
    MsgBox "Could not connect to database.", vbExclamation
    Exit Function
End If

'proceed to consume the successfully open connection

Note how Exit Sub/Exit Function are leveraged, to put a quick end to the doomed procedure’s misery… and let the rest of it confidently resume with the assurance that it’s working with an open connection, without a nesting level: having the rest of the procedure in an Else block would be redundant.

The .NET guideline about offering a pair of methods TryDoSomething/DoSomething are taken from Framework Design Guidelines, an excellent book with plenty of very sane conventions – but unless you’re writing a VBA Framework “library” project, it’s almost certainly unnecessary to include the error-throwing sister method. YAGNI: You Ain’t Gonna Need It.

Cool. Can it be abused though?

Of course, and easily so: any TryDoSomethingThatCouldNeverRaiseAnError method would be weird. Keep the Try prefix for methods that make you dodge that proverbial error-handling bullet. Parameters should generally passed ByVal, and if there’s a result to return, it should be returned as a Function procedure’s return value.

If a function needs to return more than one result and you find yourself using ByRef parameters for outputs, consider reevaluating its responsibilities: there’s a chance it might be doing more than it should. Or if the return values are so closely related they could be expressed as one thing, consider extracting them into a small class.

The GridCoord class in the OOP Battleship project is a great example of this: systematically passing X and Y values together everywhere quickly gets old, and turning them into an object suddenly gives us the ability to not only pass them as one single entity, but we also get to compare it with another coordinate object for equality or intersection, or to evaluate whether that other coordinate is adjacent; the object knows how to represent itself as a String value, and the rest of the code consumes it through the read-only IGridCoord interface – all that functionality would have to be written somewhere else, if X and Y were simply two Long integer values.

Lazy Object / Weak Reference

Sometimes a class needs to hold a reference to the object that “owns” it – i.e. the object that created it. When this happens, the owner object often needs to hold a reference to all the “child” objects it creates. If we say Class1 is the “parent” and Class2 is the “child”, we get something like this:

'Class1
Option Explicit
Private children As VBA.Collection

Public Sub Add(ByVal child As Class2)
    Set child.Owner = Me
    children.Add child
End Sub

Private Sub Class_Initialize()
    Set children = New VBA.Collection
End Sub

Private Sub Class_Terminate()
    Debug.Print TypeName(Me) & " is terminating"
End Sub

And Class2 might look like this:

'Class2
Option Explicit
Private parent As Class1

Public Property Get Owner() As Class1
    Set Owner = parent
End Property

Public Property Set Owner(ByVal value As Class1)
    Set parent = value
End Property

Private Sub Class_Terminate()
    Debug.Print TypeName(Me) & " is terminating"
End Sub

The problem might not be immediately apparent to untrained eyes, but this is a memory leak bug – this code produces no debug output, despite the Class_Terminate handlers:

'Module1
Option Explicit

Public Sub Test()
    Dim foo As Class1
    Set foo = New Class1
    foo.Add New Class2
    Set foo = Nothing
End Sub

Both objects remain in memory and outlive the Test procedure scope! Depending on what the code does, this could easily go from “accidental sloppy object management” to a serious bug leaving a ghost process running, with Task Manager being the only way to kill it! How do we fix this?

Not keeping a reference to Class1 in Class2 would fix it, but then Class2 might not be working properly. Surely there’s another way.

Suppose we abstract away the very notion of holding a reference to an object. Suppose we don’t hold an object reference anymore, instead we hold a Long integer that represents the address at which we’ll find the object pointer we’re referencing. To put it in simpler words, instead of holding the object itself, we hold a ticket that tells us where to go find it when we need to use it. We can do this in VBA.

First we define an interface that encapsulates the idea of an object reference – IWeakReference, that simply exposes an Object get-only property:

'@Description("Describes an object that holds the address of a pointer to another object.")
'@Interface
Option Explicit

'@Description("Gets the object at the held pointer address.")
Public Property Get Object() As Object
End Property

Then we implement it with a WeakReference class. The trick is to use CopyMemory from the Win32 API to take the bytes at a given address and copy them into an object reference we can use and return.

For an easy-to-use API, we give the class a default instance by toggling the VB_PredeclaredId attribute, and use a factory method to create and return an IWeakReference given any object reference: we take the object’s object pointer using the ObjPtr function, store/encapsulate that pointer address into a private instance field, and implement the IWeakReference.Object getter such that if anything goes wrong, we return Nothing instead of bubbling a run-time error.

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

#If Win64 Then
Private Declare PtrSafe Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As LongPtr)
#Else
Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)
#End If

Private Type TReference
#If VBA7 Then
    Address As LongPtr
#Else
    Address As Long
#End If
End Type

Private this As TReference

'@Description("Default instance factory method.")
Public Function Create(ByVal instance As Object) As IWeakReference
    With New WeakReference
        .Address = ObjPtr(instance)
        Set Create = .Self
    End With
End Function

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

#If VBA7 Then
Public Property Get Address() As LongPtr
#Else
Public Property Get Address() As Long
#End If
    Address = this.Address
End Property

#If VBA7 Then
Public Property Let Address(ByVal Value As LongPtr)
#Else
Public Property Let Address(ByVal Value As Long)
#End If
    this.Address = Value
End Property

Private Property Get IWeakReference_Object() As Object
' Based on Bruce McKinney's code for getting an Object from the object pointer:

#If VBA7 Then
    Dim pointerSize As LongPtr
#Else
    Dim pointerSize As Long
#End If

    On Error GoTo CleanFail
    pointerSize = LenB(this.Address)

    Dim obj As Object
    CopyMemory obj, this.Address, pointerSize

    Set IWeakReference_Object = obj
    CopyMemory obj, 0&, pointerSize

CleanExit:
    Exit Property

CleanFail:
    Set IWeakReference_Object = Nothing
    Resume CleanExit
End Property

Now Class2 can hold an indirect reference to Class1, like this:

'Class2
Option Explicit
Private parent As IWeakReference

Public Property Get Owner() As Class1
    Set Owner = parent.Object
End Property

Public Property Set Owner(ByVal Value As Class1)
    Set parent = WeakReference.Create(Value)
End Property

Private Sub Class_Terminate()
    Debug.Print TypeName(Me) & " is terminating"
End Sub

Now Module1.Test produces the expected output, and the memory leak is fixed:

Class1 is terminating
Class2 is terminating

OOP Battleship Part 4: AI Strategies

NewGame

If you recall the AIPlayer class from Part 2, the Create factory method takes an IGameStrategy parameter:

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

An AIPlayer can be created with an instance of any class that implements the IGameStrategy interface.

In any OOP language that supports class inheritance, we could have a base class e.g. GameStrategyBase, from which we could derive the various implementations, and with that we would have a place to write all the code that’s common to all implementations, …or that all implementations would possibly need to use… or not. See, class inheritance is the most important language feature that the “VBA can’t do OOP” or “VBA is not a real language” crowd love to bring up. And yet, more often than not, class inheritance isn’t the ideal solution – composition is.

And we’re going to do exactly that, by composing all IGameStrategy implementations with a GameStrategyBase class:

Battleship.AI

Coupling a game strategy with this “base” class isn’t an issue: the class is specifically meant to be used by IGameStrategy implementations. So we can shamelessly do this:

Option Explicit
Implements IGameStrategy
Private base As GameStrategyBase

Private Sub Class_Initialize()
    Set base = New GameStrategyBase
End Sub

And then proceed with implementing the PlaceShip method, given that AI player’s own PlayerGrid and the IShip the game controller is asking us to place on the grid. The base.PlaceShip method simply returns the first legal position+direction it can find.

Then we can implement the Play function to return an IGridCoord position and let the controller know what position this player is shooting at. We have a number of helper functions in GameStrategyBase we can use for that.

Random

The RandomShotStrategy shoots at random coordinates until it has located all enemy ships …then proceeds to sink them all, one after the other. It also places its ships randomly, regardless of whether the ships are adjacent or not.

Private Sub IGameStrategy_PlaceShip(ByVal grid As PlayerGrid, ByVal currentShip As IShip)

    Dim direction As ShipOrientation
    Dim position As IGridCoord
    Set position = base.PlaceShip(Random, grid, currentShip, direction)

    grid.AddShip Ship.Create(currentShip.ShipKind, direction, position)
    If grid.shipCount = PlayerGrid.ShipsPerGrid Then grid.Scramble

End Sub

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As IGridCoord
    Do
        If EnemyShipsNotAcquired(enemyGrid)  0 Then
            Set position = base.ShootRandomPosition(Random, enemyGrid)
        Else
            Set position = base.DestroyTarget(Random, enemyGrid, enemyGrid.FindHitArea)
        End If
    Loop Until base.IsLegalPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

Here the double-negative in the statement “the number of enemy ships not acquired, is not equal to zero” (WordPress is having a hard time with rendering that  operator, apparently), will probably be end up being inverted into a positive statement, which would make it read better. Perhaps If EnemyShipsToFind = 0 Then, and invert the Else logic. Or…

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As IGridCoord
    Do
        If EnemyShipsToFind(enemyGrid) > 0 Then
            Set position = base.ShootRandomPosition(Random, enemyGrid)
enemyGrid.FindHitArea)
        Else
            Set position = base.DestroyTarget(Random, enemyGrid,
        End If
    Loop Until base.IsLegalPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

That EnemyShipsToFind function should probably be a member of the PlayerGrid class.

FairPlay

The FairPlayStrategy is similar, except it will proceed to destroy an enemy ship as soon as it’s located. It also takes care to avoid placing ships adjacent to each other.

Private Sub IGameStrategy_PlaceShip(ByVal grid As PlayerGrid, ByVal currentShip As IShip)
    Do
        Dim direction As ShipOrientation
        Dim position As IGridCoord
        Set position = base.PlaceShip(Random, grid, currentShip, direction)

    Loop Until Not grid.HasAdjacentShip(position, direction, currentShip.Size)

    grid.AddShip Ship.Create(currentShip.ShipKind, direction, position)
    If grid.shipCount = PlayerGrid.ShipsPerGrid Then grid.Scramble
End Sub

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As GridCoord
    Do
        Dim area As Collection
        Set area = enemyGrid.FindHitArea

        If Not area Is Nothing Then
            Set position = base.DestroyTarget(Random, enemyGrid, area)
        Else
            Set position = base.ShootRandomPosition(Random, enemyGrid)
        End If
    Loop Until base.IsLegalPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

Merciless

The MercilessStrategy is more elaborate: it doesn’t just shoot at random – it shoots in patterns, targeting the edges and/or the center areas of the grid. It will destroy an enemy ship as soon as it’s found, and will avoid shooting in an area that couldn’t possibly host the smallest enemy ship that’s still afloat. And yet, it’s possible it just shoots a random position, too:

Private Sub IGameStrategy_PlaceShip(ByVal grid As PlayerGrid, ByVal currentShip As IShip)
    Do
        Dim direction As ShipOrientation
        Dim position As IGridCoord
        Set position = base.PlaceShip(Random, grid, currentShip, direction)
    Loop Until Not grid.HasAdjacentShip(position, direction, currentShip.Size)

    grid.AddShip Ship.Create(currentShip.ShipKind, direction, position)
    If grid.shipCount = PlayerGrid.ShipsPerGrid Then grid.Scramble
End Sub

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As GridCoord
    Do
        Dim area As Collection
        Set area = enemyGrid.FindHitArea

        If Not area Is Nothing Then
            Set position = base.DestroyTarget(Random, enemyGrid, area)
        Else
            If this.Random.NextSingle < 0.1 Then
                Set position = base.ShootRandomPosition(this.Random, enemyGrid)
            ElseIf this.Random.NextSingle < 0.6 Then
                Set position = ScanCenter(enemyGrid)
            Else
                Set position = ScanEdges(enemyGrid)
            End If
        End If

    Loop Until base.IsLegalPosition(enemyGrid, position) And _
               base.VerifyShipFits(enemyGrid, position, enemyGrid.SmallestShipSize) And _
               AvoidAdjacentHitPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

In most cases (ScanCenter and ScanEdges do), the AI doesn’t even care to “remember” the last hit it made: instead, it asks the enemy grid to give it a “hit area”. It then proceeds to analyze whether that area is horizontal or vertical, and then attempts to extend it further.

It’s Open-Source!

I uploaded the complete code to GitHub: https://github.com/rubberduck-vba/Battleship.

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.