Skip to content

VBA Moq Mocking Framework

Mathieu Guindon edited this page Jan 21, 2025 · 5 revisions

Since v2.5.92.6342 (note: there more recent releases here), Rubberduck has a very unique new feature: the popular mocking framework Moq was essentially wrapped with a COM API that can be invoked from Rubberduck unit tests to create and configure mocks for any COM object (with some caveats).

Under the hood is Moq and, transitively, Castle Windsor. These two libraries fulfill a lot of the heavy lifting; where Rubberduck comes in, is that it leverages its unit testing COM library to expose quite a lot of the power of Moq through a COM API that your VBA code can consume.

IMPORTANT!

While user code is compiled into COM objects and the framework will allow user-defined objects and interfaces to be mocked, a technical limitation with the underlying library that generates the proxy types at run-time makes it hard to work with user objects, because these objects will only be loaded once in the managed memory space, so modifying the code and recompiling will not load the updated object types on the .net side - in other words the entire host process must be restarted in order for user code changes to be taken into account.

Mocking?

You may be familiar with the concept of test stubs, where you create a fake implementation of an interface solely for tests to inject in place of whatever dependencies the code under test might have. Working with these stubs is tedious, and stubbing something complex like a worksheet can easily become a bottomless rabbit hole. Stubs are a great tool, but mocks are a whole other level.

With mocking, there is no concrete implementation: instead, the framework uses your instructions to create and configure a stub implementation of literally any object. This is mind-blowing black magic stuff: with just a few lines of code, you can mock Excel.Application and completely control every single one of its members.

Curious? Let's jump right into it.


Quick Start

At the top of the API we find the Rubberduck.MockProvider class, which will now get automatically initialized in any new test module you add to your VBA projects. The class you'll use to configure mocks is Rubberduck.ComMock, and you will always get one from the provider, like so (early bound for clarity):

Option Explicit
'Private Assert As Rubberduck.AssertClass
'Private Fakes As Rubberduck.FakesProvider
Private Mocks As Rubberduck.MockProvider

'@ModuleInitialize
Private Sub ModuleInitialize()
    'this method runs once per module.
    'Set Assert = New Rubberduck.AssertClass
    'Set Fakes = New Rubberduck.FakesProvider
    Set Mocks = New Rubberduck.MockProvider
End Sub

'@TestMethod("Uncategorized")
Public Sub TestMethod1()
    'arrange
    Dim Mock As Rubberduck.ComMock
    Set Mock = Mocks.Mock("Excel.Application") 'here we create a new mock using the Excel.Application progid

    'then we configure our mock as per our needs...
    Mock.SetupWithReturns "Name", "Mocked-Excel"
    Mock.SetupWithCallback "CalculateFull", AddressOf OnAppCalculate

    Dim Mocked As Excel.Application
    Set Mocked = Mock.Object 'ComMock.Object represents the mocked object and always implements the COM interface it's mocking

    'act

    'just making sure the mock works :)
    Debug.Print Mocked.Name
    Mocked.CalculateFull

    'it would normally look more like this: we inject the mocked dependency into the object we want to test in isolation.
    'With SomeMacro.Create(Mocked) 
    '    .Execute
    'End With

    'assert
    'use the ComMock.Verify method to fail the test if a method that was setup was not invoked as per the test's specifications:
    Mock.Verify "CalculateFull", Mocks.Times.AtLeastOnce

End Sub

Public Sub OnAppCalculate()
    'we can use AddressOf to implement callbacks that the mock will invoke instead of the concrete method:
    Debug.Print "A full recalc was made by the mocked Excel.Application instance."
End Sub

As you can see it's a very similar principle as the Fakes API, except we're not hooking any libraries here, no: instead we're spawning a .net type that implements Excel.Application on the fly, telling it what to do when such or such member is invoked, and then we can validate that things actually happened as expected.

Let's dig deeper now.


Rubberduck.MockProvider

The top-level object for the mocking API has the following members:

MockProvider.Mock

Function Mock(ProgId As String, [Project As String]) As ComMock

This method creates and returns a new mock for a specified interface or progID (or GUID) string.

  • ProgId is a String parameter that can be any valid input for CreateObject; for user code it would be the name of the class to mock.
  • Project is an optional String parameter; for user code, it serves to disambiguate class names that could be the same but in separate projects.

MockProvider.Times

Property Times() As Rubberduck.Times

This read-only property exposes the Times methods, which are used together with the ComMock.Verify method to specify how a test should fail:

  • Function AtLeast(CallCount As Long) As Times
  • Function AtLeastOnce() As Times
  • Function AtMost(CallCount As Long) As Times
  • Function AtMostOnce() As Times
  • Function Between(MinCallCount As Long, MaxCallCount As Long, [RangeKind As SetupArgumentRange = SetupArgumentRange_Inclusive]) As Times
  • Function Exactly(CallCount As Long) As Times
  • Function Never() As Times
  • Function Once() As Times

SetupArgumentRange

This enum is used to describe whether a range of values should include or exclude its boundaries:

  • SetupArgumentRange_Inclusive = 0
  • SetupArgumentRange_Exclusive = 1

MockProvider.It

This get-only property exposes the SetupArgumentCreator API, which allows for many flexible ways to specify exactly how a mocked method is supposed to be invoked by the code under test:

  • Function Is(Value) sets up an argument that must be the specified value
  • Function IsAny() sets up a placeholder argument that does not need to have any particular value
  • Function IsIn(Values() As variant) sets up an argument that must be one of the specified values (use VBA.Array() to specify them inline)
  • Function IsInRange(Start, End, Range As SetupArgumentRange) sets up an argument that must be within a range of values
  • Function IsNotIn(Values() As Variant) sets up an argument that must not be any of the specified values
  • Function IsNotNull() sets up an argument that must be any non-null (Nothing) object reference

All these functions create and return a SetupArgumentDefinition object.

MockProvider.SetupArgumentDefinition

This class encapsulates the metadata for an argument, including its type and values. The type is a SetupArgumentType enum constant that describes how the argument should be validated:

  • SetupArgumentType_Is = 0
  • SetupArgumentType_IsAny = 1
  • SetupArgumentType_IsIn = 2
  • SetupArgumentType_IsInRange = 3
  • SetupArgumentType_IsNotIn = 4
  • SetupArgumentType_IsNotNull = 5

The Property Values() As Variant() read-only array holds the arguments needed to perform the operations.

MockProvider.SetupArgumentDefinitions

This class represents an enumerable collection (should work with For Each) of SetupArgumentDefinition objects, exposing a Count and an Item(Index As Long) default property.

Rubberduck.ComMock

An object of this type is returned by the MockProvider.Mock function, which serves as a factory method for creating mocks. A COM mock has the following members:

ComMock.Object

Property Object() As Object

Gets a reference to the mocked COM object; this reference is exposed as Object, but can always safely be cast to the mocked interface type.

ComMock.ProgId

Property ProgId() As String

Gets a string that represents a valid CreateObject target, or the name of a class in the user's VBA project.

WARNING!
The managed (.net Framework) proxy types will only be generated ONCE in the lifetime of the host process. While this works fine for compiled type libraries, avoid mocking (writing? see SOLID:OCP) user-code interfaces that are prone to require frequent modifications, because you'll need to shutdown and restart Excel and Rubberduck before you can run unit tests against the updated interface.

ComMock.Project

Property Project() As String

Gets a string that represents, for user code, the identifier name of the VBA project associated with a provided ProgId (class name).

WARNING!
The managed (.net Framework) proxy types will only be generated ONCE in the lifetime of the host process. While this works fine for compiled type libraries, avoid mocking (writing? see SOLID:OCP) user-code interfaces that are prone to require frequent modifications, because you'll need to shutdown and restart Excel and Rubberduck before you can run unit tests against the updated interface.

ComMock.Setup

Sub Setup(Name As String, [Args])

Specifies a setup on the mocked type for a call to a method that does not return a value.

Use this method to configure a member call on the mock, that does not return a value (so, a Sub or Property Let/Set procedure).

NOTE
Use MockProvider.It to specify the Args of all Setup and Verify methods.

ComMock.SetupChildMock

Function SetupChildMock(Name As String, [Args]) As ComMock

Specifies a setup on the mocked type for a call to an object member of the specified object type.

Use this method to configure a member call on the mock, that returns an object reference; the returned object will also be mocked. This function also returns the configured mock, so multiple setup calls can be chained in the same instruction.

ComMock.SetupWithCallback

Sub SetupWithCallback(Name As String, Callback As LongLong, [Args])

Specifies a callback (use the AddressOf operator) to invoke when the method is called that receives the original invocation

IMPORTANT! The callback must be a public procedure defined in a standard module.

ComMock.SetupWithReturns

Sub SetupWithReturns(Name As String, Value, [Args])

Specifies a setup on the mocked type for a call to a value-returning method.

Use this method to configure a member call on the mock so that it returns a specific value.

ComMock.Verify

Sub Verify(Name As String, Times As Times, [Args])

Verifies that a specific invocation matching the given arguments was performed on the mock.

Fails the test if a specific invocation did or did not happen, as specified.


Clone this wiki locally