Making MVVM Work in VBA Part 2: Event Propagation

Using a WithEvents variable to handle the MSForms.Control events of, say, a TextBox control has the irritating tendency to throw a rather puzzling run-time error 459 “Object or class does not support the set of events”. To be honest, I had completely forgotten about this when I started working on this MVVM framework. I had even posted an answer on Stack Overflow and my learning-it-the-hard-way is immortalized on that page.

…there’s a bit of COM hackery going on behind the scenes; there’s enough smokes & mirrors for VBA to successfully compile the above, but, basically, you’re looking at a glitch in The Matrix (Rubberduck’s resolver has similar “nope” issues with MSForms controls): there isn’t any obvious way to get VBA to bind a dynamic control object to its MSForms.Control events.

-Mathieu Guindon, Apr 18 ’19 

What I hadn’t noticed until today, was that another user had posted an answer to that question a few hours later that day – and that answer ultimately leads to the groundbreaking manual wiring-up of what VBA normally does automagically under the hood when we declare a WithEvents variable.

pUnk’d

The code I’m about to share is heavily based on the work shared on Stack Overflow by user Evr, and uses the ConnectToConnectionPoint Win32 API that, it must be mentioned, comes with a caveat:

This function is available through Windows XP and Windows Server 2003. It might be altered or unavailable in subsequent versions of Windows.

Regardless, it works (for now anyway, …if we lose Mac support for this specific capability).

Rubberduck uses similar connection points to handle a number of VBE events that aren’t otherwise exposed, so I knew this was going to work one way or another. The idea is to pass an IUnknown pointer to an object that exposes members with very specific VB_UserMemId attribute values, and have accordingly very specific member signatures.

This post lists a bunch of such attributes – however since there aren’t any problems with binding regular TextBox and CommandButton events (these do work with simple WithEvents event providers), I’m only interested in these:

EventVB_UserMemId
AfterUpdate-2147384832
BeforeUpdate-2147384831
Enter-2147384830
Exit-2147384829
The VB_UserMemId attribute values for each of the MSForms.Control events.

This is going to be a little bit lower-level than usual, but every VBA user class has an IUnknown pointer, So we can use any class module that has the members with the appropriate VB_UserMemId attribute values, and pass that as the pUnk pointer argument.

So, here’s the punk in question, exactly as I currently have it:

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "ControlEventsPunk"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Attribute VB_Description = "Provides an event sink to relay MSForms.Control events."
'@Folder MVVM.Infrastructure.Win32
'@ModuleDescription "Provides an event sink to relay MSForms.Control events."
'based on https://stackoverflow.com/a/51936950
Option Explicit
Implements IControlEvents
Private Type GUID
    Data1 As Long
    Data2 As Integer
    Data3 As Integer
    Data4(0 To 7) As Byte
End Type
'[This function is available through Windows XP and Windows Server 2003. It might be altered or unavailable in subsequent versions of Windows.]
'https://docs.microsoft.com/en-us/windows/win32/api/shlwapi/nf-shlwapi-connecttoconnectionpoint
#If VBA7 Then
Private Declare PtrSafe Function ConnectToConnectionPoint Lib "shlwapi" Alias "#168" (ByVal Punk As stdole.IUnknown, ByRef riidEvent As GUID, ByVal fConnect As Long, ByVal PunkTarget As stdole.IUnknown, ByRef pdwCookie As Long, Optional ByVal ppcpOut As LongPtr) As Long
#Else
Private Declare Function ConnectToConnectionPoint Lib "shlwapi" Alias "#168" (ByVal punk As stdole.IUnknown, ByRef riidEvent As GUID, ByVal fConnect As Long, ByVal punkTarget As stdole.IUnknown, ByRef pdwCookie As Long, Optional ByVal ppcpOut As Long) As Long
#End If
Private Type TState
    RefIID As GUID 'The IID of the interface on the connection point container whose connection point object is being requested.
    Connected As Boolean
    PunkTarget As Object
    Cookie As Long
    
    Handlers As Collection
End Type
'from https://stackoverflow.com/a/61893857 (same user as #51936950!)
Private Const ExitEventID As Long = -2147384829
Private Const EnterEventID As Long = -2147384830
Private Const BeforeUpdateEventID As Long = -2147384831
Private Const AfterUpdateEventID As Long = -2147384832
Private This As TState
'@Description "Gets/sets the target MSForms.Control reference."
Public Property Get Target() As Object
Attribute Target.VB_Description = "Gets/sets the target MSForms.Control reference."
    Set Target = This.PunkTarget
End Property
Public Property Set Target(ByVal RHS As Object)
    Set This.PunkTarget = RHS
End Property
'@Description "Registers the listener."
Public Function Connect() As Boolean
Attribute Connect.VB_Description = "Registers the listener."
    GuardClauses.GuardNullReference This.PunkTarget, TypeName(Me), "Target is not set."
    ConnectToConnectionPoint Me, This.RefIID, True, This.PunkTarget, This.Cookie, 0&
    This.Connected = This.Cookie <> 0
    Connect = This.Connected
End Function
'@Description "De-registers the listener."
Public Function Disconnect() As Boolean
Attribute Connect.VB_Description = "De-registers the listener."
    If Not This.Connected Then Exit Function
    ConnectToConnectionPoint Me, This.RefIID, False, This.PunkTarget, This.Cookie, 0&
    This.Connected = False
    Disconnect = True
End Function
'@Description "A callback that handles MSForms.Control.AfterUpdate events for the registered target control."
Public Sub OnAfterUpdate()
Attribute OnAfterUpdate.VB_UserMemId = -2147384832
Attribute OnAfterUpdate.VB_Description = "A callback that handles MSForms.Control.AfterUpdate events for the registered target control."
    Dim Handler As IHandleControlEvents
    For Each Handler In This.Handlers
        Handler.HandleAfterUpdate
    Next
End Sub
'@Description "A callback that handles MSForms.Control.BeforeUpdate events for the registered target control."
Public Sub OnBeforeUpdate(ByVal Cancel As MSForms.ReturnBoolean)
Attribute OnBeforeUpdate.VB_UserMemId = -2147384831
Attribute OnBeforeUpdate.VB_Description = "A callback that handles MSForms.Control.BeforeUpdate events for the registered target control."
    Dim Handler As IHandleControlEvents
    For Each Handler In This.Handlers
        Handler.HandleBeforeUpdate Cancel
    Next
End Sub
'@Description "A callback that handles MSForms.Control.Exit events for the registered target control."
Public Sub OnExit(ByVal Cancel As MSForms.ReturnBoolean)
Attribute OnExit.VB_UserMemId = -2147384829
Attribute OnExit.VB_Description = "A callback that handles MSForms.Control.Exit events for the registered target control."
    Dim Handler As IHandleControlEvents
    For Each Handler In This.Handlers
        Handler.HandleExit Cancel
    Next
End Sub
'@Description "A callback that handles MSForms.Control.Enter events for the registered target control."
Public Sub OnEnter()
Attribute OnEnter.VB_UserMemId = -2147384830
Attribute OnEnter.VB_Description = "A callback that handles MSForms.Control.Enter events for the registered target control."
    Dim Handler As IHandleControlEvents
    For Each Handler In This.Handlers
        Handler.HandleEnter
    Next
End Sub
'@Description "Registers the specified object to handle the relayed control events."
Public Sub RegisterHandler(ByVal Handler As IHandleControlEvents)
Attribute RegisterHandler.VB_Description = "Registers the specified object to handle the relayed control events."
    This.Handlers.Add Handler
End Sub
Private Sub Class_Initialize()
    Set This.Handlers = New Collection
    This.RefIID.Data1 = &H20400
    This.RefIID.Data4(0) = &HC0
    This.RefIID.Data4(7) = &H46
End Sub
Private Sub IControlEvents_OnAfterUpdate()
    OnAfterUpdate
End Sub
Private Sub IControlEvents_OnBeforeUpdate(ByVal Cancel As MSForms.IReturnBoolean)
    OnBeforeUpdate Cancel
End Sub
Private Sub IControlEvents_OnEnter()
    OnEnter
End Sub
Private Sub IControlEvents_OnExit(ByVal Cancel As MSForms.IReturnBoolean)
    OnExit Cancel
End Sub
Private Sub IControlEvents_RegisterHandler(ByVal Handler As IHandleControlEvents)
    RegisterHandler Handler
End Sub

Let’s ignore the IControlEvents interface for now. The class has a Target – that’ll be our TextBox control instance. So we set the Target, and then we can invoke Connect, and when we’re done we can invoke Disconnect to explicitly undo the wiring-up.

Then we have an OnEnter method with VB_UserMemId = -2147384830, which makes it an event handler procedure for MSForms.Control.Enter. The name of the procedure isn’t relevant, but it’s important that the procedure is parameterless.

Similarly, the name of the OnExit procedure has no importance, but it must have a single ByVal Cancel As MSForms.ReturnBoolean parameter (only ByVal and the data type matter). For events that have more than one parameter, the order is also important.

In theory that’s all we need: we could go on and handle Control.Exit in this OnExit procedure, and call it a day. In fact you can probably do that right away – however I need another step for my purposes, because I’m going to need my PropertyBindingBase class to propagate these events “up” to, say, some TextBoxPropertyBinding class that can implement some TextBox-specific behavior for the Control events.

Propagating Events

I had already a working pattern for my INotifyPropertyChange requirements to propagate property changes across objects, and the pattern is applicable here too. See, I could have declared a Public Event Exit(ByRef Cancel As MSForms.ReturnBoolean) on the ControlEventsPunk class, and then I could have used a WithEvents variable to handle them – and that would have worked too. Except I don’t want to use events here, because events work well as implementation details… but they can’t be exposed on an interface, which makes them actually more complicated to work with.

There are two interfaces: one that defines the “events” and exposes a method to register “handlers”, and the other mandates the presence of a callback for each “event”. For INotifyPropertyChange the handler interface was named IHandlePropertyChange, so I went with IControlEvents and IHandleControlEvents.

So, the “provider” interface looks like this:

'@Folder MVVM.Infrastructure.Bindings.Abstract
'@ModuleDescription "Provides the infrastructure to relay MSForms.Control events."
Option Explicit
Public Sub RegisterHandler(ByVal Handler As IHandleControlEvents)
End Sub
Public Sub OnEnter()
End Sub
Public Sub OnExit(ByVal Cancel As MSForms.ReturnBoolean)
End Sub
Public Sub OnAfterUpdate()
End Sub
Public Sub OnBeforeUpdate(ByVal Cancel As MSForms.ReturnBoolean)
End Sub

And then the “handler” interface looks like this:

'@Folder MVVM.Infrastructure.Bindings.Abstract
'@ModuleDescription "An object that can be registered as a handler for IControlEvents callbacks."
Option Explicit
Public Sub HandleEnter()
End Sub
Public Sub HandleExit(ByVal Cancel As MSForms.ReturnBoolean)
End Sub
Public Sub HandleAfterUpdate()
End Sub
Public Sub HandleBeforeUpdate(ByVal Cancel As MSForms.ReturnBoolean)
End Sub

So, looking back at the ControlEventsPunk class, we find that the implementation for RegisterHandler consists in adding the provided Handler object to an encapsulated Collection that holds all the registered handlers; when we “handle” a control event, we iterate all registered handlers and invoke them all in a sequence. When an event has a Cancel parameter, the last handler that ran gets the final say on whether the parameter should be True or False, and each handler receives the Cancel value that was set by the previous handler than ran.

This is a slightly different paradigm than your regular VBA/VB6 auto-wired events, where one event only ever has one handler: now these work more like the multicast delegates that events are in .NET, with an “invocation list” and the ability to add/remove (although, I haven’t implemented the removal) handlers dynamically at run-time – except the “handlers” are full-fledged VBA objects here, rather than .NET delegates.

Whenever the MVVM infrastructure needs to propagate events, I use this pattern instead. This was my first time actually implementing an Observer Pattern, and hadn’t even realized! (thanks Max!) – that isn’t a pattern you see often in event-capable languages, but I can definitely see this proven, solid abstraction (Java developers would probably be rather familiar with that one) become my new favorite go-to pattern to expose events on an interface in VBA… But there’s probably a reason the first time I come across a situation where that pattern is really handy (and actually needed, for testability), is when I’m writing framework-level (i.e. an API intended to be used by code that isn’t written yet) code that’s very much as deep into the OOP rabbit hole as I’ve ever been in VBA (or any other language for that matter)… and there’s still no rock bottom in sight.

In any case, now that we have a way to handle and propagate control events, we can have MVVM property bindings that can format TextBox.Text on exit, i.e. we can have a ViewModel that knows SomeProperty has a value of 25.59, and the Text property of the bound textbox control can say $25.59 just by specifying a FormatString (like “Currency”, for example) when we create the binding.

For the next post in this series I think we’re ready to deep-dive into the actual binding mechanics, and I’ll have the updated MVVM infrastructure code on GitHub by then.

About Class Modules

What is a class?

The term is known to everyone that read anything about programming in VBA. It defines objects, yes. But what else do we know about them? What don’t we know about them?

VBA being built on top of COM has a number of implications, and explains a number of language features and the mechanics around classes and objects. Let’s dive into what makes a class module, and what being written in a class module means for your code.


Metadata

In order to define a class, a class module needs to contain metadata, information that VBA will use when it needs to create an object. This metadata is thoroughly specified in MS-VBAL section 4.2.

If we add a new class module to a VBA project, name it Thing, then export the code file, it should look something like this (minus Option Explicit if you don’t have the “require variable declaration” VBE setting enabled for some reason):

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

This VERSION 1.0 CLASS is the header VBA is looking for – if you export a standard module, it will not have that header. It won’t have the BEGIN...END block that follows either.

MultiUse = -1 is controlled by the Instancing property, which you can find in the Properties toolwindow:

VBA supports two values for this property (VB6 has more, depending on the project type):

  • Private (default)
  • PublicNotCreateable

By default, a VBA class is private, thus only visible / only exists in the project in which it’s defined. In an add-in project, this is useful for a private/internal API. When an add-in project needs to be referenced from other VBA projects, it needs a public API – provided by PublicNotCreateable class modules. These classes can be used in referencing projects, but you can only New them up in the project they’re defined in.

We could imagine that, if a class module’s property grid had more rows than that, the other values would all be listed between the BEGIN and END keywords. So where’s the (Name) coming from?

Attribute VB_Name = "Thing"

The Attribute token, as per specifications, must always appear at the beginning of a line. Attribute names are a bit cryptic, and they’re not all specified or well-documented. In fact, different VBA host applications may support different attributes… but all VBA implementations support VB_Name and the attributes that control instantiation:

  • VB_GlobalNameSpace (false)
  • VB_Createable (false if public)
  • VB_PredeclaredId (false by default)
  • VB_Exposed (true if public)

3 of these 4 attributes are controlled by the Instancing property. VB_PredeclaredId is normally False, but special classes such as a UserForm have it set to True; the VBE provides no tooling to manipulate this attribute, but VBA will honor its value if you modify it manually (or if Rubberduck does it for you).

Instance

The instancing property of the class module determines whether & how the class is able to be instantiated; an instance of a class is an object that is defined by that class. In VBA you can create a new object with the New keyword or the CreateObject function – but CreateObject will not work with VBA user code, because the instancing modes supported in VBA don’t allow it.

Being an object, an instance of a class can only ever exist at run-time. Objects only ever exist at run-time.

There are several ways objects can come into existence in VBA.

  • Issued to the left-hand side of a Set assignment, using a New keyword or a CreateObject function call on the right-hand side;
  • Issued to a With block from a New keyword or CreateObject function call;
  • On the first encounter (or first since last destruction) of the name of a class module with the VB_PredeclaredId attribute value set to True;
  • On the first encounter (or first since last destruction) of an object reference declared with As New;

Similar to how an Excel project’s ThisWorkbook module “inherits” the Workbook members, VBA classes “inherit” a standard “VB user class” that provides two hooks on two particularly important stages in the object’s lifetime: Initialize, and Terminate.

Private Sub Class_Initialize()
End Sub

Private Sub Class_Terminate()
End Sub

Given this code:

Private Sub Test()
    Dim foo As Class1
    Set foo = New Class1

    With New Class1
    End With
End Sub

The Initialize handler would run twice – once at New Class1 as the right-hand-side of the Set assignment is being evaluated, so before the foo reference is assigned. Then once more at New Class1 in the With block, as the block is entered but before the object reference is captured by the With block.

The Terminate handler would first run at End With for the With instance, and the foo instance would terminate at End Sub, because that’s where it’s going out of scope (and it’s not Set to Nothing before that, and nothing else is keeping alive a reference to the object).

Keep in mind that declarations aren’t executable statements, so this code runs both handlers exactly 0 times:

Private Sub Test()
    Dim foo As New Class1
End Sub

The As New object is only actually created where foo is first referenced. If Class1 exposed a Public Sub DoSomething() method, and the above procedure had foo.DoSomething under the declaration, Initialize would run at the dereferencing operator (.), just before the member call to the DoSomething method; the Terminate handler would run at End Sub.

Auto-instantiated objects (declared with As New), like the default instance of class modules with a PredeclaredId attribute set to True, are re-created whenever they are no longer in scope but suddenly need to exist again:

Private Sub Test()
    Dim foo As New Class1
    foo.DoSomething
    Set foo = Nothing
    Debug.Print foo Is Nothing
End Sub

Without As New, the foo.DoSomething member call would be made against Nothing and this code would raise run-time error 91. Because of As New, the assignment to Nothing does terminate the object instance, but a new one is spawned again when foo is dereferenced again – so even though the object was just destroyed, the Debug.Print statement correctly (but confusingly) outputs False, since merely referencing the object foo has caused VBA to re-create it behind your back.

This behavior is marginally useful, but definitely not as obvious at it should be: that is why Rubberduck warns about As New declarations.


Members

The members of a class are the fields (module variables), properties, and methods of the class – whether private or public. Fields should be Private and encapsulate the instance state. Property Get members can expose private fields in a read-only manner, and Function and Sub procedures are dubbed methods.

Avoid write-only properties; if external code can write to a property, it should be able to read that value back.

A class module can define a default member by specifying a VB_UserMemId member attribute with a value of 0 (or with Rubberduck, by simply adding a '@DefaultMember annotation/comment). For collection classes, convention is to have an Item property as the default member, such that things(i) is equivalent to things.Item(i). The hidden attribute, like all attributes, is only visible when the code file is exported to be viewed in a text editor that isn’t the VBE:

'@DefaultMember
Public Property Get Item(ByVal index As Variant) As Variant
Attribute Item.VB_UserMemId = 0
    '...
End Property

In any other case, default members should be avoided: a class with a default member can be let-coerced into a value, and this easily makes things confusing – especially when considering that a default member might be returning an object that itself has a default member, that returns an object, that itself has a default member, that returns an object, …the compiler needs to work some recursive logic just to resolve what types/classes are involved: needless to say, us mere puny humans reading the code, understandably have no idea.

Let-coercion happens when you try to evaluate an object as a value expression, for example:

Debug.Print Application

We know that this instruction prints “Microsoft Excel” just like it would if we fully spelled out Debug.Print Application.Name, but we can’t know how. We can’t, because if we inspect the Application class in the Object Browser, we find that its default property is a hidden _Default get-only String property, and we can only best-guess that the implementation of that property is yielding the Name property. The result is an opaque API that does things implicitly, and nobody knows what these things are. This is bad, because at face value, Debug.Print Application makes no sense as a statement if we know that Application is an object.

If we try to let-coerce an object that doesn’t have a default member, we get run-time error 438 “object doesn’t support this property or method”, which we normally see when a late-bound member call fails. An with a hidden default member, we ensure that the inner workings of our APIs remain an arcane black box for everyone consuming our APIs. Don’t do this to your future self.

Without this language feature, the Set keyword wouldn’t be needed – assigning an object reference would never be ambiguous!

Dim rng As Variant
rng = Sheet1.Range("A1:A10") 'ambiguous: is rng the Range or its default value?
Set rng = Sheet1.Range("A1:A10") 'unambiguous: definitely the Range reference

Interfaces

Every class defines a default interface – the Public members determine what’s on that interface. When a variable is declared As Class1, the members available to IntelliSense are the members of the default interface of Class1. Interfaces cannot expose fields and/or events, so if a class defines public fields, they are exposed as read/write properties; events are simply ignored.

An interface defines how an object can interact with the outside world – or rather, how the outside world can interact with an object: it’s like a boundary, an interface between the object and its client. The object encapsulates state, its interface allows the outside world to manipulate it.

Having a default interface implies that objects can have non-default interfaces, too: an object can implement as many interfaces as needed. In VBA that’s done with the Implements keyword. And because every class defines a public interface, any class can implement any other.

Say we had a Thing class, we would declare an object variable of that type like this:

Dim instance As Thing
Set instance = New Thing

This makes the compiler understand that when we access the instance object, we are seeing it through the lens of its default Thing interface, so the member we get in the drop-down list when we type the . dereferencing operator in instance., are the public members defined in the Thing class module.

If Thing implemented an ISomething interface, and we declared it like this:

Dim instance As ISomething
Set instance = New Thing

We would still be looking at a Thing, however we would now be seeing it through the lens of its ISomething interface, and the members we would get in the drop-down list when we typed instance., would be the public members defined in the ISomething class module.

The benefits of this might seem very much theoretical and far-fetched if we’re coming from purely procedural programming, but from a COM standpoint, this is very much Tuesday – meaning, declaring explicit interfaces that formally define how we intend the outside world to be able to interact with our objects, is standard practice. .NET code intended to be consumed by COM, makes a cleaner API when it defines explicit interfaces.

When a class defines a public interface, but no implementation for these members, we give that class a generic name that we traditionally prefix with a very much Hungarian I. This makes it easy to identify purely abstract classes (interfaces) in a sea of modules. With Rubberduck’s Code Explorer, classes that are implemented by other classes, as well as classes annotated with an '@Interface annotation/comment, get a special dedicated “interface” icon that can help easily identify interface modules in a code base, prefixed or not.

This prefixing tradition was carried into modern practices, and you will find this I prefix everywhere in the .NET framework, just as you will find it in a lot of (often hidden) classes in standard VBA libraries – so in order to blend in and deliver a clear consistent message to the reader/maintainer, interface class module names should be prefixed with an I:

If you dig into the hidden classes of the Excel type library, you will find hidden interfaces that expose members that should look familiar: IAppEvents, IWorkbookEvents, IChartEvents, ICommandBarEvents, IDocEvents, IOLEObjectEvents, and many others; these hidden interfaces are your biggest clue about how interfaces and events are related, and indirectly, about how events work under COM: this mechanism explains why a VBA interface cannot expose events directly. So what are events then?


Events

Easily the very first aspect of writing VBA code we are exposed to, event handler procedures are defined by a special implicit interface that we specify in VBA code using the Event keyword in a class module. When we type the space following the RaiseEvent keyword, the editor assists by listing the members of that interface:

Raising an event can be seen as a special kind of call statement that invokes a callback – a procedure that’s written in some other class module: an event handler procedure, that may or may not execute code that we know nothing about. The handler procedure runs synchronously, so the next statement to run after a RaiseEvent statement, will run after the handler procedure has returned (this is particularly useful for events that define a ByRef cancel As Boolean parameter)… unless the handler bombed:

Option Explicit
Public Event Something(ByVal foo As String, ByVal bar As Long)

Public Sub DoSomething()
    On Error Resume Next
    RaiseEvent Something("foo", 42)
    Debug.Print "done"
End Sub

This is where the notion of callback matters: the above code will never print “done” if a handler runs into an unhandled error – execution will simply stop (and VBA will pop that familiar “unhandled error” box). If the Something handler were a “normal” procedure call, “done” would get printed whether or not an error was unhandled in the procedure.

We can handle Workbook events in the ThisWorkbook document class module, because the code of ThisWorkbook already includes every member of a Workbook class, even before we write a single line of code in it:

Debug.Print TypeOf ThisWorkbook Is Excel.Workbook 'True

This type of class inheritance unfortunately isn’t possible with VBA user code, but we can also express the relationship with composition, if we visualize the ThisWorkbook module like this:

Option Explicit
Private WithEvents Workbook As Workbook

Private Sub Class_Initialize()
    Set Workbook = Me
End Sub

The net effect being that in the ThisWorkbook module we have a Workbook event provider we can pick from the left-hand side code pane drop-down, listing the available events in the right-hand side drop-down – exactly as if there was an implicit WithEvents Workbook private field in any other class module:

ThisWorkbook module handling Workbook events for itself.
Class1 module handling Workbook events for a given Workbook object reference.

We use the WithEvents keyword to declare an object variable for which we would like to handle events. The keyword is only legal in class modules (this includes document class modules and userform modules), and the As clause may only specify a class that exposes public events. Moreover, an auto-instantiated object cannot be declared WithEvents, so As New is also illegal.

Events/callbacks are particularly useful to make application components that don’t “see” each other, still be able to talk to each other and interact: the class that’s raising an event doesn’t know if there’s someone answering the call on the other side, even less who that someone is and what they do for a living. They are a tool that can help decoupling components… to an extent: the problem is that in VBA classes, events are essentially considered implementation details – they are not exposed on the class’ default interface, even though they’re Public: the only class that is allowed to access an event, is the class that defines it – no other class can raise an event, unless we expose a method specifically for that:

Public Event Something()

Public Sub OnSomething()
    RaiseEvent Something
End Sub

Public Sub DoSomething()
    OnSomething()
    '...
End Sub

The Event and WithEvents keywords provide language-level assistance with the otherwise relatively complex wiring-up of callbacks. In order to use them with interfaces, we can use an adapter pattern with formalized SomethingEvents interfaces – like how the Battleship project demonstrates with the GridViewAdapter and IGridViewEvents classes.


Everything You Ever Wanted To Know About Events

VBA is often said to be an event-driven language: a lot of worksheet automation involves executing code in response to such or such workbook or worksheet event. ActiveX controls such as MSForms.CommandButton are trivially double-clicked, and code is written in some CommandButton1_Click procedure.

But how does it all work, and can we leverage this event-driven paradigm in our own code too? But first, what is this paradigm all about?

Asynchronous Code

In a procedural paradigm, code executes one statement at a time, top to bottom, in sequence: procedure A gets invoked, procedure A calls procedure B, procedure B completes, execution returns to procedure A, procedure A completes, execution ends. That’s a paradigm you’re likely already familiar with.

In an event-driven paradigm, code still executes one statement at a time, in the very same way – except now procedures are being invoked by an external object, and there isn’t always a way to tell at compile-time what the run-time sequence will be. If you’re writing the code-behind for a UserForm module with Button1 and Button2 controls, there is no way to know whether Button1_Click will run before Button2_Click, or if either are even going to run at all: what code gets to run, is driven by what events get raised – hence, event-driven.

Event-driven code is asynchronous, meaning you could be in the middle of a loop, and then a DoEvents statement is encountered, and suddenly you’re not in the loop body anymore, but (as an example) in some worksheet event handler that gets invoked when the selected cell changes. And when that handler completes, execution resumes in the loop body, right where it left off.

This mechanism is extremely useful, especially in an object-oriented project, since only objects (class modules) are allowed to raise and handle events. It is being put to extensive use in the OOP BattleShip project (see GridViewAdapter and WorksheetView classes for examples of event forwarding and how to define an interface that exposes events), which I’m hoping makes a good advanced-level study on the matter.

But let’s start at the beginning.

Host Document & Other Built-In Events

Whether you’re barely a week into your journey to learn VBA, or several years into it, unless all you ever did was record a macro, you’ve been exposed to VBA events.

VBA code lives in the host document, waiting to be executed: any standard module public procedure that can be invoked without parameters can be an entry point to begin code execution – these are listed in the “macros” list, and you can attach them to e.g. some Shape and have the host application invoke that VBA code when the user clicks it.

But macros aren’t the only possible entry points: the host document often provides “hooks” that you can use to execute VBA code when the host application is performing some specific operation – like opening a new document, saving it, modifying it, etc.: different hosts allow for various degrees of granularity on “hooking” a varying amount of operations. These “hooks” are the events exposed by the host application’s object model, and the procedures that are executed when these events are raised are event handler procedures.

Document Modules

In Excel the host document is represented by a Workbook module, named ThisWorkbook; every worksheet in this workbook is represented by a Worksheet module. These document modules are a special type of class module in that they inherit a base class: the ThisWorkbook class is a Workbook class; the Sheet1 class is a Worksheet class – and when classes relate to each other with an “is-a” relationship, we’re looking at class inheritance (“has-a” being composition). So document modules are a very special kind of module, first because their instantiation is in the hands of the host application (you can’t do Set foo = New Worksheet to create a new sheet), and second because like UserForm modules, they are inheriting the members of a base class – that’s how you can type Me. in a procedure inside an otherwise empty document module, and get plenty of members to pick from: if you’re in the Sheet1 module, you have access to Me.Range, and that Range property is inherited from the Worksheet “base class”. Or Me.Controls in the UserForm1 module, inherited from the UserForm class.

Wait I thought VBA didn’t support inheritance?

Indeed, VBA user code doesn’t have any mechanism in the language to support this: there’s no Inherits keyword in VBA. But VBA creates and consumes COM types, and these types can very well be pictured as having an inheritance hierarchy.

Or something like it. Picturing the ThisWorkbook : Workbook relationship as though there was a hidden Private WithEvents Workbook As Workbook field in the ThisWorkbook module, i.e. more like composition than inheritance, wouldn’t be inaccurate either.

Fair enough. So what does this have to do with events?

Take any old Sheet1 module: because it “inherits” the Worksheet class, it has access to the events defined in that class. You can easily see what events are available in any class, using the Object Browser (F2) – all events are members represented with a lightning bolt icon:

The Worksheet.Activate event is raised when the Worksheet.Activate method is invoked.

So when you’re in a Worksheet module, you can implement event handlers for any events fired by the base Worksheet class. Because of how events work under the hood, in order for an event handler to “hook” the event it means to handle, it must have the correct signature or at least, a compatible one: the name of the procedure, the number, order, and type of its parameters must match exactly with the signature/definition of the event to be handled… and ensuring that isn’t as complicated as it sounds:

All available event sources (left) and corresponding events (right) can be selected from dropdowns at the top of the code pane: the VBE generates a procedure with the correct signature automatically!

Notice the VBE generates Private procedures: there is no reason whatsoever to ever make an event handler public. Event handler procedures are meant to handle events, i.e. they’re callbacks whose intent is to be invoked by the VBA runtime, not by user code! That’s why I recommend limiting the amount of logic that you put into an event handler procedure, and having the bulk of the work into a separate, dedicated procedure that can be made public if it needs to be invoked from elsewhere. This is especially important for UserForm modules, which tend to be accessed from outside the form’s code-behind module.

Event handler procedures are always named in a very specific way, just like interface implementations:

Private Sub EventProvider_EventName()

Note the underscore: it matters, on a syntactical level. This is why you should avoid underscores in procedure names, and name all procedures in PascalCase. Adhering to this naming standard will spare you many headaches later, when you start defining and impementing your own interfaces (spoiler: your project will refuse to compile if you try implementing an interface that has members with an underscore in their name).

Custom Events

Any VBA class module can define its own events, and events may only be defined in a class module (remember: document and userform modules are classes). Defining events is done using the (drumroll) Event keyword:

Public Event BeforeSomething(ByRef Cancel As Boolean)
Public Event AfterSomething()

You’ll want the events Public, so they can be handled in other classes. Now all that’s left to do is to raise these events. That’s done using the RaiseEvent keyword:

Public Sub DoSomething()
    Dim cancelling As Boolean
    RaiseEvent BeforeSomething(cancelling)
    If Not cancelling Then
        'do stuff...
        RaiseEvent AfterSomething
    End If
End Sub

Here are a few guidelines (that word is chosen) for sane event design:

  • DO define Before/After event pairs that are raised before and after a given operation. This leaves the handlers the flexibility to execute preparatory/cleanup code around that operation.
  • DO provide a ByRef Cancel As Boolean parameter in Before events. This lets the handlers determine whether an operation should be cancelled or not.
  • CONSIDER using ByVal Cancel As MSForms.ReturnBoolean if the MSForms type library is referenced. Being a simple object encapsulating the cancel state, it can be passed by value, and the handler code can treat it as a Boolean if it wants to, because the object’s Value is the class’ default member.
  • CONSIDER exposing a public On[EventName] procedure with the same signature as the event, whose purpose is simply to raise said event; events can only be raised by the class they are defined in, so such methods are very useful for making an object raise an event, notably for testing purposes.
  • DO use past tense to indicate that an event occurs after a certain operation has completed, when there is no need for an event to occur before. For example: Changed instead of Change.
  • DO use future tense to indicate that an event occurs before a certain operation has started, when there is no need for an event to occur after. For example: WillConnect.
  • DO NOT use present tense (be it indicative or progressive/continuous), it’s ambiguous and unclear exactly when the event is raised in the operation. For example, a lot of standard library events use this naming scheme, and it’s easy to second-guess whether the event is fired before or after said Change or Changing has actually happened.
  • DO NOT use Before or After without also exposing a corresponding After/Before event.
  • DO NOT mistake guidelines for gospel, what really matters is consistency.

The class that defines an event is the provider; a class that handles that event is a client. The client code needs to declare a WithEvents field – these fields must be early-bound, and the only types available for the As clause are event providers, i.e. classes that expose at least one event.

Option Explicit
Private WithEvents foo As Something

Private Sub foo_BeforeDoSomething(ByRef Cancel As Boolean)
    'handles Something.DoSomething
End Sub

Every WithEvents field adds a new item in the left-hand code pane dropdown, and that class’ events are displayed in the right-hand code pane dropdown – exactly like any plain old workbook or worksheet event!