Interfaces in VBA - How to use them and how to work around them

BitsqueezerDatabase Developer
CERTIFIED EXPERT
Published:
We live in a world of interfaces like the one in the title picture. VBA also allows to use interfaces which offers a lot of possibilities. This article describes how to use interfaces in VBA and how to work around their bugs.

Modules.zip


Table of Contents


1      About CC Interface V1.0

1.1      Features of CCInterface

1.2      Requirements

2      General information

2.1      What is an "Interface"?

2.2      What does that mean for programmers?

2.2.1        Example Interface

2.2.2        Example Module Implementing the Interface

2.2.3        Example Module using the Interface

2.2.4        Advantages of Interfaces

2.3      Why an interface can be useless in VBA

2.3.1        Issues with "Implements"

2.3.2        Possible Methods to Workaround

2.4      Enough of Workarounds

3      How to use

3.1      How it works

3.1.1        The Idea

3.1.2        How to Use

       1. Adjusting VBA References

       2. Using in your own Access file

       3. First create the interface wrapper class module

       4. Second rewrite the code in the class module using the interface

       5. Third rewrite the code using the interface anywhere

       6. Final work


1. About CC Interface V1.0


The purpose of CCInterface is to completely replace the standard interface technology built in into VBA. Not that the interfaces which you can insert into your code using the "Implements" statement are not a really useful technology. It would be a very great feature if it would work without problems. Unfortunately at least with Access 2010 (and maybe later versions) interfaces in VBA are full of bugs and can destroy your project.


This is where the CCInterface module comes in whose purpose is to allow using interfaces without the "Implements" statement so that your code is stable without loosing the possibility of using interfaces.


1.1 Features of CCInterface

  • Checks the implementation of an interface in a class module
  • Converts a class module by changing the normally as "Private" declared objects (subs, function, properties) into "Public" declarations
  • Creates a new interface wrapper class module and inserts the required code into this wrapper class and also into the class module which uses the interface
  • Disables the "Implements" statement with a comment character (')


1.2 Requirements

  • Needs a reference to "Microsoft Visual Basic for Applications Extensibility" (only during design time)
  • Please always make a backup of your database file before trying to use CCInterface!


2 General information


2.1 What is an "Interface"?


An interface object is an object that should be used by different other objects for the same purpose. It gives these different objects the opportunity to be used in a specific standard way.


To give an example from the real world: If you want to listen to your favorite music you need a device which outputs sound. This can be, for example, a pair of loudspeakers or a headphone. These devices cannot produce music, they only offer the ability to output sound.


So you now also need a device that can play music. This could be a CD player or an MP3 player. Both have no device to output the music as sound so you need your headphones or loudspeakers. To get them connected, you need an object between them, a phone jack plug and a socket. (So these are in fact two interfaces, the plug on the speaker side and the socket on the player side. To not make it too complicated we handle it as one interface here.)


The interface has itself no functionality. It cannot produce sound and it cannot play. But it offers both objects (two players and two speaker systems here) the same standard possibilities; to be connected with each other and to forward the sound signal to the output.


So the interface object offers to the player a way to be connected to speakers or headphones, and in the same way it offers to the headphones a way to use an MP3 or CD player (and a lot of others). All players and all output devices will use the same interface so the manufacturers of an output device don't need to think about what player it will be interfaced with nor do the manufacturers of the players need to think about which output device will be connected.


2.2 What does that mean for programmers?


An interface in a programming language like VBA is a collection of procedures (subs, functions or properties). In opposite to normal class modules it usually doesn't contain its own code, it only contains the empty procedures with all parameters, as needed.


The sense of an interface is to provide what the name says: an interface, not code. It should only describe the interface generally without being itself an active object.


That means: If you create an MP3 player class then your class module provides the functionality to output audio from a given file. Your interface class module (an interface is always a class module) is a 3.5mm phone jack which should be used from an output class. The interface module itself is a "dead" module  which itself does simply nothing. It is also named a "contract" between the one and the other class module which wants to use it - therefore it doesn't contain any code.


2.2.1 Example Interface

Option Compare Database
Option Explicit

' This should be used to inform the objects that the
' program should be closed now.
Public Sub BeforeQuitProgram(ByRef Cancel As Boolean)
End Sub


Create a new class module in the VBA editor and insert the code above. We name it "IStdFunctions" here (usually interface class modules are named with a big "I" at the beginning of the name).


This should be used to tell the using object module that we want to quit the application before it really does. Moreover it contains a "Cancel" parameter which should give the using object the opportunity to avoid that the program will be closed (maybe because the user needs to decide what to do with unsaved data).


You have now created your interface. Really. That's it, nothing else. That was easy.


2.2.2 Example Module Implementing The Interface


Now how you can insert the new "phone jack" into your module?


At first, using an interface is only possible to class modules. Fortunately these are not only pure class modules but also forms and reports which have a code module - these are also class modules (that's the reason why you can open more than one equal form at the same time).


So we create a blank form now, name it "frmTest"  and set the "Has Module" property of the form to "Yes" which immediately creates the class module which you can see in the list in the VBA editor (Form_frmTest).


The code for the form is also not complicate for now:

Option Compare Database
Option Explicit

Implements IStdFunctions

The code contains only the "Implements" statement which tells VBA that the interface class "IStdFunctions" should be used in this class module.


Try to compile your VBA code (using the "Debug" menu) now and you'll get an error message which says that you need to insert the "BeforeQuitProgram" sub in your form's class module (it will only tell you about the first missing procedure, so if your interface module will have more procedures it reports about the next missing code in the next try to compile if you only inserted this one).


So what "Implements" also does is that it tells the compiler which procedures needs to be implemented. You can find a list if you open the left drop-down list in the VBA editor where you'll find "IStdFunction" (because of the "Implements" statement) which you need to select. Then you'll find all procedures of the interface in the right drop-down list:



Selecting the procedure will insert it into your form code now, but because we only have one it was already inserted by selecting the interface name. If you would have more you would need to select each entry one by one until all are inserted (inserted are displayed in bold font in the drop-down list).


This is the code which was inserted:

Private Sub IStdFunctions_BeforeQuitProgram(Cancel As Boolean)
End Sub


You can now compile your project because now the contract is fulfilled, all procedures of your interface module are implemented into the form module now.


But if you read the code more thoroughly you'll see that there are differences between the form's code and the code in the interface module:

  • The sub is declared as "Private"
  • The name of the sub has the prefix "IStdFunctions_"


This has the following reasons:

  • It is "Private" because these procedures should not be seen externally. You can see that if you try to access "Me.IStdFunctions_BeforeQuitprogram" - IntelliSense will not show that in the list as "Me" also it is only able to see the "Public" procedures, the same as any external object trying to access it. Of course you can directly call the sub internally by leaving out "Me." as any other private sub in the form - but you shouldn't do that. Try to never call an interface procedure directly without using the interface in the way it should (explained later), in the same way as you never should directly call an event procedure like "Form_Load" and let the event happen with the forms loads organically. In both cases it is easy to be reached by creating an additional procedure and using it in Form_Load and the other procedure, the same with interface procedures.
  • The prefix "IStdFunctions_" should make the procedure unique in your form's code. Maybe you want to implement another interface later which itself also has a sub "BeforeQuitProgram" - this would not be possible if you doesn't have a unique name.


2.2.3 Example Module Using The Interface


So now you have an interface class module and a form which implements your interface. We now need a third module that wants to use the interface. This can also be a standard module so please create a standard module named "modTest" now.


This is the code for the new standard module:

Option Compare Database
Option Explicit

Public Sub TestIStdFunctions()
    Dim objIStdFunctions As IStdFunctions
    Dim frm As Form_frmTest

    DoCmd.OpenForm "frmTest"
    Set frm = Forms("frmTest")
    Set objIStdFunctions = frm
    Stop
End Sub

Run the code now, it will break at the "Stop" command highlighting it.


Now you can go to the immediate window and if you enter "objIStdFunctions." you will see the following:



This is the only sub which is in the interface object so no surprise.


You can call that here now if you enter "objIStdFunctions.BeforeQuitProgram False". Nothing happens, because there's no code implementation anywhere. But what did we do in the test sub above?


First we declared two object variables, one as the interface class and one as the specific form class.

Then the form is opened and the "frm" variable is assigned to the opened form. You can now look into the IntelliSense list if you type "frm." into the immediate window, you'll not find the "IStdFunctions" as described above as it is declared "Private".


Now the speciality of the interface classes is used: We do not write "Set objIStdFunctions As New IStdFunctions" as we would expect for any normal class. Instead we assign the form reference of the loaded form which is in the "frm" variable to the object variable of the interface class. This couples all procedures which are in the form module belonging to the interface class to the object variable. So using "BeforeQuitProgram" doesn't start anything in the interface class "IStdFunction", instead it calls the (privately declared!) sub "IStdFunctions_BeforeQuitProgram" sub in the form module!


That's cool, isn't it? You now have an alternative way of calling a list of procedures in a form. But that you could also have done by "normal" methods like declaring these procedures as "Public". So what are the advantages of using an interface now?


2.2.4 Advantages Of Interfaces


First, the interface is not dependent on your form. You can implement it into any other kind of class modules, too, so you could also insert that on the same way to a report or to a general class module.


In the same way as the MP3 player uses the phone jack, the CD player or mobile phone or amplifier could insert the phone jack. But internally they may need to do different things to fulfil the "contract" with the interface; maybe the CD player must initiate the CD load, or the MP3 player needs to load a file and decode it, or the amplifier needs to look for the activated sound source and route that to the phone jack - but in the end the interface does the same for all devices: It outputs the sound exactly the same for each device.


That's the same here; you want to tell different objects to be informed about quitting the program. So you could add the form reference "frm" and also a report reference "rpt" (created with OpenReport etc. on the same way) into a collection and then use this:

Dim bolCancel As Boolean

For Each objIStdFunctions In MyCollection
    objIStdFunctions.BeforeQuitProgram bolCancel
    If bolCancel then Exit Sub
Next

All completely different objects in the collection use the same functionality, they all can be used as interface objects and they all can decide how the functionality is implemented in their specific instances. The form may look for unsaved data and set the "Cancel" variable to "True" if the user must do anything here before stopping the program, the report may stop printing the report and clear the printer queue for example.


The module using the interface doesn't need to know anything about the specific objects, it only uses the interface as this would be the only list of existing procedures. The specific object (like the form implementing the interface) doesn't need to know who has called the interface code and doesn't need to access it directly in any way (it can't as it has no reference to it). You could also provide a reference to the calling module if you want to access anything from there - without knowing what it is if this also has an interface to communicate with.


In this way you could, for example, exchange information between modules, e.g. a form and a popup form where the popup form should be given an ID to display and the popup form should return a chosen ID to the calling form without knowing which form it was. So the popup form could be used for two different main forms which should select a supplier for example and return the chosen supplier without directly accessing the specific main form - because you forward a reference to the main form's interface object only using an interface of the popup form and the popup form accesses this interface object reference only and can be sure that it will be sent to the right main form.


This decouples the code of both forms completely so it is never a problem to rename a control on the main or the popup form as both never accesses a control name of the other form directly.


2.3 Why an interface can be useless in VBA


2.3.1 Issues With "Implements"


Really great what you can do with an interface and how it can make your life easier and the code more stable.


"Stable" is unfortunately the big problem using interfaces. As it is a not often used feature of VBA it seems that it is not really tested by the Microsoft developers thoroughly. At least with Access 2010 (never had this issue with A2007) and maybe later versions using the "Implements" statement creates some really bad issues which are nearly impossible to solve.

  • if you use "Implements" very often in a bigger project the project gets into a state where it is not possible to keep it compiled. You can compile it, save it, no problem. If you close Access and reopen your project and look into the "Debug" menu it is not compiled again (you can see that because the "Compile" entry is not greyed out again).
  • If the project is not compiled like described above Access crashes in many cases when you try to open the module where the interface is implemented. Sometimes it works if you open e.g. a form without an implemented interface and then open the form with the interface.
  • Sometimes the project seems to be compiled when you open the VBA editor first and everything seems to work. But if you open the project without opening the VBA editor, then opening the form using the interface again crashes Access.
  • Sometimes only deactivating the "Implements" command makes a form displaying the contents and reactivating it again keeps the form from displaying records.
  • Not to mention that inserting an interface procedure using the drop-down sometimes creates "RHA" as parameter name instead of the name defined in the interface class.


2.3.2 Possible Methods To Workaround


  • You can try to decompile the project with a copy of course and then compile it again. Sometimes it helps for a while.
  • You can try to export all objects with "Application.SaveAsText" and reimport them with "Application.LoadFromText" in a new database file, the compile it again. Sometimes it helps for a while.
  • You can try to add a space into the "Implements" line so it creates a syntax error, leave the line, go back, remove the syntax error and compile it again. You'll see that it takes a lot longer to compile as now all interface codes are compiled again. Sometimes this helps to get the namespace of VBA corrected and it works for a while.
  • You can try to deactivate all "Implements" statements in the entire project using "find and replace" and then compile it, reactivate all again and compile it again, maybe close and open the project in-between. That helps for a while - maybe...


2.4 Enough Of Workarounds


After using all these workarounds for month I now decided to create my own one, the CCInterface modules.

I wanted to be sure that I can provide the functionality of a normal interface so that I don't need to reprogram my whole project which is a lot code. I also don't wanted to loose the interface technology in general as I'm a fan of the idea. So this is why I programmed this little tool to help me doing that.


3 How to use


3.1 How it works


3.1 The Idea


As I cannot implement my own code into the VBA compiler I need to use what I have and that is that I need to use a class module.


So instead of rewriting the code I created a wrapper class which should be the replacement of the real interface class. So in our example above with "IStdFunctions" I add a class module "IStdFunctions_Wrapper" which also contains all procedures of the normal interface class but additionally it also contains a reference to the object using it (e.g. a form reference) and code to call the objects in the form (or whatever class module using the interface).


Unfortunately that would need to make all the interface procedures originally declared as "Private" to "Public" which is of course against the rules of a real interface as they now could be called from everywhere. But this is something I can live with as long as the rest is the same as before.


The code of the wrapper interface class ("IStdFunctions_Wrapper") would look like this:

Option Compare Database
Option Explicit

' --------- Interface Wrapper for interface IStdFunctions------------
Private prv_objWithInterface As Object

Public Property Get ObjWithInterface() As Object
    Set ObjWithInterface = prv_objWithInterface
End Property
Public Property Set ObjWithInterface(obj As Object)
    Set prv_objWithInterface = obj
End Property

' This should be used to inform the objects that the
' program should be closed now.

Public Sub BeforeQuitProgram(ByRef Cancel As Boolean)
    If Not prv_objWithInterface Is Nothing Then
        prv_objWithInterface.IStdFunctions_BeforeQuitProgram Cancel
    End If
End Sub

So we have a private variable to save the object's reference (a form in this example) and public properties to handle it (using properties would also allow to add more code to handle the reference, otherwise a public variable would also be enough).


Next, we need the form implementing the interface. It already exists, we have created that above. It has the "Implements" statement and the procedure from the old interface. The wrapper should now handle this so we need to change the code a little bit:

Option Compare Database
Option Explicit

'Implements IStdFunctions

Private prv_objIStdFunctions_Wrapper As IStdFunctions_Wrapper

Public Property Get ObjIStdFunctions() As IStdFunctions_Wrapper
    If prv_objIStdFunctions_Wrapper Is Nothing Then
        Set prv_objIStdFunctions_Wrapper = New IStdFunctions_Wrapper
        Set prv_objIStdFunctions_Wrapper.ObjWithInterface = Me
    End If
    Set ObjITest1 = prv_objIStdFunctions_Wrapper
End Property

Public Sub IStdFunctions_BeforeQuitProgram(Cancel As Boolean)
End Sub

The difference is that the interface sub is now declared as "Public" and a new object variable for the wrapper class module is created and a property which automatically initialises it if it was not created before or lost due an unhandled error (of course unhandled errors only exist during design time...). Moreover the "Implements" statement is deactivated with a comment character.


Next the module using the interface need a little change:

Option Compare Database
Option Explicit

Public Sub TestIStdFunctions()
    Dim ObjIStdFunctions As IStdFunctions_Wrapper
    Dim frm As Form_frmTest
   
    DoCmd.OpenForm "frmTest"
    Set frm = Forms("frmTest")
    Set ObjIStdFunctions = frm.ObjIStdFunctions
    Stop
End Sub

The difference here is that the interface object variable is now changed to "IStdFunctions_Wrapper" and the assignment is extended by the new property "ObjIStdFunctions" above.


If you run the "TestIStdFunctions" sub now and reach the "Stop" you can now access the new interface like before. IntelliSense also displays only the interface procedures and you could also use "For Each" like in 2.2.4, only you would need to not add the form/report reference directly to the collection, instead you would add "frm.ObjIStdFunctions" or "rpt.ObjIStdFunctions". If you want to use more than one interface in the For loop you could add the form and report references to the collection and use "For Each obj in MyCollection" where "obj" is declared as "Object" and then use "obj.ObjIStdFunctions" or "obj.ObjIOtherInterface".


3.1.2 How To Use


As there is a lot to do to rewrite all the procedures in the project that already heavily use the interface I wrote this class to automate a lot of those issues.


1. Adjusting VBA References



To use it you must check the references in VBA ("Tools" - "References") and add the "Microsoft Visual Basic for Applications Extensibility 5.3" reference (or whatever version you have, 5.3 here).


This is only needed at design time, you can remove the reference and the two "CCInterface" modules for the final release of your project.


If you've adjusted the references, start "Debug" - "Compile" to make sure the code is compiled and all references are correct.


2. Using in your own Access file


Before using it please make sure that you have created a backup of your project in a safe place, I'm not responsible if your project gets broken.


As this tool doesn't use specific features of newer versions of Access it should work in all Access versions.


For now you need to insert the code modules "modCCInterface" and "clsCCInterface" into your project. It is also recommended to insert the "modRecreate" module which I wrote to create a new ADP from an existing one by exporting and importing all objects and settings. It has the sub "procRecreateSaveAllAsText" procedure which only does the export. Calling that before using CCInterface makes sure you also have a textual backup of all your objects. As it was written for ADPs it cannot export tables or queries, but at least all forms, reports, macros and modules.


3. First create the interface wrapper class module


Go to the immediate window and use this command to create the interface wrapper class from your interface module. In this example I use the "IStdFunctions" interface of the previous examples:

CCIF.CreateInterfaceWrapper "IStdFunctions"

That's all, the new interface class module "IStdFunctions_Wrapper" should now exist in the module list in the VBA editor.

Compile and save the code now.


4. Second rewrite the code in the class module using the interface


That's as easy as above:

CCIF.RewriteModuleWithInterface "IStdFunctions", "Form_frmTest"

In this example the form "frmTest" was rewritten to use the wrapper instead. That means, the deactivated "Implements", the new property and variable "ObjIStdFunctions" and all interface procedures are now Public.


You now need to do that for any object using the interface, don't forget to compile and save before you go on to the next object.


5. Third rewrite the code using the interface anywhere


That was not as easy as the above steps. The module can find the object that declares " As IStdFunctions" and rewrite that. But as there are many possibilities to initialize and use that, it only rewrites the declaration and adds a "TODO:" comment to it so you can easily find that and add the adjustment (adding ".ObjIStdFunctions" when assigning the reference).

To rewrite the declarations you can use this one:

CCIF.ReplaceInterfaceUsageWithWrapper "IStdFunctions"


6. Final work


  • As explained in 3.1.2.5 you need to adjust the reference assignments on your own.
  • If you have functions in your interface that are not using standard variables like "Long", "String" etc. and that need a "Set" statement, you need to add the "Set" into the wrapper interface class on your own. e.g. If your return type is "DAO.Recordset" you will get a Set property and a "Set" statement in properties, but as there is no way to distinguish between a Set or Let in functions by VBE the CCInterface code would need to decide if it would need a let or set here so I added also a "TODO" comment here instead and always use Let in all cases. As you only add the interface wrapper code once, this is only a little work to do.
  • If you've converted everything you can remove the "modCCInterface", "clsCCInterface" and "modRecreate" modules and remove the above inserted reference.


 In future, if you want to insert a new module with the interface and you already have the wrapper module you can use "Implements" to insert all the procedures, before compiling that to check if everything is OK. 

Then:

  • Change the "Private"s to "Public"s for all interface procedures 
  • Copy and paste the header code (the private variable declaration "prv_objIStdFunctions" in the example and the "ObjIStdFunctions" properties) from another module and deactivate the "Implements". Of course you can also copy the interface procedures from another module instead of using "Implements" to do that. 
  • If you have not removed the CCInterface modules you can also use that to do the job.
1
8,269 Views
BitsqueezerDatabase Developer
CERTIFIED EXPERT

Comments (2)

You wrote "Access 2010 (and maybe later versions)". Have you had the possibility to proove that behaviour with Access 2013 or later meanwhile? Maybe the problems don't exist there any more?
BitsqueezerDatabase Developer
CERTIFIED EXPERT

Author

Commented:
Hi,

no, I cannot say if that problem still exists. As the problem came up in a large project with a lot of modules it may also not appear in smaller projects. But on the other hand Microsoft did not change much in VBA since years so it is very likely that the problem still exists (and also because interfaces are not so much known/used by VBA programmers).

Cheers,

Christian

Have a question about something in this article? You can receive help directly from the article author. Sign up for a free trial to get started.