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!