Can we use Interfaces and Events together at the same time? Can we use Interfaces and Events together at the same time? vba vba

Can we use Interfaces and Events together at the same time?


This is a perfect use-case for an Adapter: internally adapting the semantics for a set of contracts (interfaces) and exposing them as its own external API; possibly according to some other contract.

Define class modules IViewEvents:

Option Compare DatabaseOption ExplicitPrivate Const mModuleName   As String = "IViewEvents"Public Sub OnBeforeDoSomething(ByVal Data As Object, ByRef Cancel As Boolean):  End SubPublic Sub OnAfterDoSomething(ByVal Data As Object):                            End SubPrivate Sub Class_Initialize()    Err.Raise 5, mModuleName, AccessError(5) & "-Interface class must not be instantiated."End Sub

IViewCommands:

Option Compare DatabaseOption ExplicitPrivate Const mModuleName   As String = "IViewCommands"Public Sub DoSomething(ByVal arg1 As String, ByVal arg2 As Long):   End SubPrivate Sub Class_Initialize()    Err.Raise 5, mModuleName, AccessError(5) & "-Interface class must not be instantiated."End Sub

ViewAdapter:

Option Compare DatabaseOption ExplicitPrivate Const mModuleName   As String = "ViewAdapter"Public Event BeforeDoSomething(ByVal Data As Object, ByRef Cancel As Boolean)Public Event AfterDoSomething(ByVal Data As Object)Private mView       As IViewCommandsImplements IViewCommandsImplements IViewEventsPublic Function Initialize(View As IViewCommands) As ViewAdapter    Set mView = View    Set Initialize = MeEnd FunctionPrivate Sub IViewCommands_DoSomething(ByVal arg1 As String, ByVal arg2 As Long)    mView.DoSomething arg1, arg2End SubPrivate Sub IViewEvents_OnBeforeDoSomething(ByVal Data As Object, ByRef Cancel As Boolean)    RaiseEvent BeforeDoSomething(Data, Cancel)End SubPrivate Sub IViewEvents_OnAfterDoSomething(ByVal Data As Object)    RaiseEvent AfterDoSomething(Data)End Sub

and Controller:

Option Compare DatabaseOption ExplicitPrivate Const mModuleName       As String = "Controller"Private WithEvents mViewAdapter As ViewAdapterPrivate mData As ObjectPublic Function Initialize(ViewAdapter As ViewAdapter) As Controller    Set mViewAdapter = ViewAdapter    Set Initialize = MeEnd FunctionPrivate Sub mViewAdapter_AfterDoSomething(ByVal Data As Object)    ' Do stuffEnd SubPrivate Sub mViewAdapter_BeforeDoSomething(ByVal Data As Object, ByRef Cancel As Boolean)    Cancel = Data Is NothingEnd Sub

plus Standard Modules Constructors:

Option Compare DatabaseOption ExplicitOption Private ModulePrivate Const mModuleName   As String = "Constructors"Public Function NewViewAdapter(View As IViewCommands) As ViewAdapter    With New ViewAdapter:   Set NewViewAdapter = .Initialize(View):         End WithEnd FunctionPublic Function NewController(ByVal ViewAdapter As ViewAdapter) As Controller    With New Controller:    Set NewController = .Initialize(ViewAdapter):   End WithEnd Function

and MyApplication:

Option Compare DatabaseOption ExplicitPrivate Const mModuleName   As String = "MyApplication"Private mController As ControllerPublic Function LaunchApp() As Long    Dim frm As IViewCommands     ' Open and assign frm here as instance of a Form implementing     ' IViewCommands and raising events through the callback interface     ' IViewEvents. It requires an initialization method (or property     ' setter) that accepts an IViewEvents argument.    Set mController = NewController(NewViewAdapter(frm))End Function

Note how use of the Adapter Pattern combined with programming to interfaces results in a very flexible structure, where different Controller or View implementations can be substituted in at run time. Each Controller definition (in the case of different implementations being required) uses different instances of the same ViewAdapter implementation, as Dependency Injection is being used to delegate the event-source and command-sink for each instance at run time.

The same pattern can be repeated to define the relationship between the Controller/Presenter/ViewModel and the Model, though implementing MVVM in COM can get rather tedious. I have found MVP or MVC is usually better suited for COM-based applications.

A production implementation would also add proper error handling (at a minimum) to the extent supported by VBA, which I have only hinted at with the definition of the mModuleName constant in each module.


An interface is, strictly speaking and only in OOP terms, what an object exposes to the outside world (i.e. its callers/"clients").

So you can define an interface in a class module, say ISomething:

Option ExplicitPublic Sub DoSomething()End Sub

In another class module, say Class1, you can implement the ISomething interface:

Option ExplicitImplements ISomethingPrivate Sub ISomething_DoSomething()    'the actual implementationEnd Sub

When you do exactly that, notice how Class1 doesn't expose anything; the only way to access its DoSomething method is through the ISomething interface, so the calling code would look like this:

Dim something As ISomethingSet something = New Class1something.DoSomething

So ISomething is the interface here, and the code that actually runs is implemented in the body of Class1. This is one of the fundamental pillars of OOP: polymorphism - because you could very well have a Class2 that implements ISomething in a wildly different way, yet the caller wouldn't ever need to care at all: the implementation is abstracted behind an interface - and that's a beautiful and refreshing thing to see in VBA code!

There are a number of things to keep in mind though:

  • Fields are normally considered as implementation details: if an interface exposes public fields, implementing classes must implement a Property Get and a Property Let (or Set, depending on the type) for it.
  • Events are considered implementation details, too. Therefore they need to be implemented in the class that Implements the interface, not the interface itself.

That last point is rather annoying. Given Class1 that looks like this:

'@Folder StackOverflowDemoPublic Foo As StringPublic Event BeforeDoSomething()Public Event AfterDoSomething()Public Sub DoSomething()End Sub

The implementing class would look like this:

'@Folder StackOverflowDemoImplements Class1Private Sub Class1_DoSomething()    'method implementationEnd SubPrivate Property Let Class1_Foo(ByVal RHS As String)    'field setter implementationEnd PropertyPrivate Property Get Class1_Foo() As String    'field getter implementationEnd Property

If it's any easier to visualize, the project looks like this:

Rubberduck Code Explorer

So Class1 might define events, but the implementing class has no way of implementing them - that's one sad thing about events and interfaces in VBA, and it stems from the way events work in COM - events themselves are defined in their own "event provider" interface; so a "class interface" can't expose events in COM (as far as I understand it), and therefore in VBA.


So the events must be defined on the implementing class to make any sense:

'@Folder StackOverflowDemoImplements Class1Public Event BeforeDoSomething()Public Event AfterDoSomething()Private foo As StringPrivate Sub Class1_DoSomething()    RaiseEvent BeforeDoSomething    'do something    RaiseEvent AfterDoSomethingEnd SubPrivate Property Let Class1_Foo(ByVal RHS As String)    foo = RHS    End PropertyPrivate Property Get Class1_Foo() As String    Class1_Foo = fooEnd Property

If you want to handle the events Class2 raises while running code that implements the Class1 interface, you need a module-level WithEvents field of type Class2 (the implementation), and a procedure-level object variable of type Class1 (the interface):

'@Folder StackOverflowDemoOption ExplicitPrivate WithEvents SomeClass2 As Class2 ' Class2 is a "concrete" implementationPublic Sub Test(ByVal implementation As Class1) 'Class1 is the interface    Set SomeClass2 = implementation ' will not work if the "real type" isn't Class2    foo.DoSomething ' runs whichever implementation of the Class1 interface was suppliedEnd SubPrivate Sub SomeClass2_AfterDoSomething()'handle AfterDoSomething event of Class2 implementationEnd SubPrivate Sub SomeClass2_BeforeDoSomething()'handle BeforeDoSomething event of Class2 implementationEnd Sub

And so we have Class1 as the interface, Class2 as the implementation, and Class3 as some client code:

Rubberduck Code Explorer

...which arguably defeats the purpose of polymorphism, since that class is now coupled with a specific implementation - but then, that's what VBA events do: they are implementation details, inherently coupled with a specific implementation... as far as I know.


Because bounty is already headed for Pieter's answer I'll not attempt to answer the MVC aspect of the question but instead the headline question. The answer is Events have limits.

It would be harsh to call them "syntactic sugar" because they save a lot of code but at some point if your design gets too complex then you have to bust out and manually implement the functionality.

But first, a callback mechanism (for that is what events are)

modMain, the entry/starting point

Option ExplicitSub Main()    Dim oClient As Client    Set oClient = New Client    oClient.RunEnd Sub

Client

Option ExplicitImplements IEventListenerPrivate Sub IEventListener_SomethingHappened(ByVal vSomeParam As Variant)    Debug.Print "IEventListener_SomethingHappened " & vSomeParamEnd SubPublic Sub Run()    Dim oEventEmitter As EventEmitter    Set oEventEmitter = New EventEmitter    oEventEmitter.ServerDoWork MeEnd Sub

IEventListener, the interface contract that describes the events

Option ExplicitPublic Sub SomethingHappened(ByVal vSomeParam As Variant)End Sub

EventEmitter, the server class

Option ExplicitPublic Sub ServerDoWork(ByVal itfCallback As IEventListener)    Dim lLoop As Long    For lLoop = 1 To 3        Application.Wait Now() + CDate("00:00:01")        itfCallback.SomethingHappened lLoop    NextEnd Sub

So how does WithEvents work? One answer is to look in the type library, here is some IDL from Access (Microsoft Access 15.0 Object Library) defining the events to be raised.

[  uuid(0EA530DD-5B30-4278-BD28-47C4D11619BD),  hidden,  custom(0F21F359-AB84-41E8-9A78-36D110E6D2F9, "Microsoft.Office.Interop.Access._FormEvents")    ]dispinterface _FormEvents2 {    properties:    methods:        [id(0x00000813), helpcontext(0x00003541)]        void Load();        [id(0x0000080a), helpcontext(0x00003542)]        void Current();    '/* omitted lots of other events for brevity */};

Also from Access IDL here is the class detailing what its main interface is and what is event interface is, look for source keyword, and VBA needs a dispinterface so ignore one of them.

[  uuid(7398AAFD-6527-48C7-95B7-BEABACD1CA3F),  helpcontext(0x00003576)]coclass Form {    [default] interface _Form3;    [source] interface _FormEvents;    [default, source] dispinterface _FormEvents2;};

So what that is saying to a client is that operate me via the _Form3 interface but if you want to receive events then you, the client, must implement _FormEvents2. And believe it or not VBA will when WithEvents is met spin up an object that implements the source interface for you and then route incoming calls to your VBA handler code. Pretty amazing actually.

So VBA generates a class/object implementing the source interface for you but questioner has met the limits with the interface polymorphism mechanism and events. So my advice is to abandon WithEvents and implement you own callback interface and this is what the given code above does.

For more information then I recommend reading a C++ book that implements events using the connection point interfaces, your google search terms are connection points withevents

Here is a good quote from 1994 highlighting the work VBA does I mentioned above

After slogging through the preceding CSink code, you'll find that intercepting events in Visual Basic is almost dishearteningly easy. You simply use the WithEvents keyword when you declare an object variable, and Visual Basic dynamically creates a sink object that implements the source interface supported by the connectable object. Then you instantiate the object using the Visual Basic New keyword. Now, whenever the connectable object calls methods of the source interface, Visual Basic's sink object checks to see whether you have written any code to handle the call.

EDIT: Actually, mulling my example code you could simplify and abolish the intermediate interface class if you do not want to replicate the way COM does things and you are not bothered by coupling. It is after all just a glorified callback mechanism. I think this is an example of why COM got a reputation for being overly complicated.