Parallel Processing MS Access VBA Application
Adding paralell processing capability to MS Access VBA code.
Motivation
I got a challenging assignment to provide alarm capability on top of an existing application, written in VBA Access. This required a few issues to be dealt with and resolved. I will, in this article, describe the steps I took to provide parallel processing, i.e., alarm capabilities to an existing MS Access application.
Accompanying Code
The accompanying code is an MS Access application written in MS Office 2007, and saved as a .mdb so it can be accessed from within MS Access 2003. The C# code is written in the beta version of VS 2010.
Assumption about the Reader
I assume that your experience is more extensive in the VBA side than on C# side.
Issues to Resolve
The issues for providing parallel processing to VBA code stems from the fact that MS Office does not support concurrency. As such, we will need to provide:
- A mechanism that will monitor key events in order to trigger the parallel process (the secondary process).
- The parallel process itself (the secondary process) needs to be capable of being interrupted.
- The existing system (the primary VBA driven system) should not experience noticeable degradation in performance when the secondary, parallel, process is introduced.
A Bad Solution (that does not work)
At first glance, one might be tempted to create a hidden form, and set its timer function to provide the needed parallel processing. This will not work if the hidden form performs a long running process, as MS Access is a singly processing environment, and having this hidden form threading through a long-running Sub/Function will prevent other Subs/Functions from running.
We can resort to the DoEvents
function in order to yield and allow MS Access to pay attention to some other Sub/Function. However, I feel that this is a really bad idea, a really-really bad idea. By resorting to the DoEvents
function to achieve parallelism, we commit to using the DoEvents
function in all lengthy Subs/Functions, in the primary or secondary parallel process. This practice is impractical, a maintenance nightmare, and worst of all, it potentially compromises integrity. This is not the main point of the article, so I will not elaborate. For the interested reader, read the paragraph under Caution in http://office.microsoft.com/en-us/access/HA012288271033.aspx.
Solution in the Theoretical Realm
- We will create a hidden form that will monitor the event(s) that will trigger the parallel, long running process.
- We will create a .NET DLL that will encapsulate the long running process, a process that is interruptible.
- The existing VBA application's processing will not be noticeably degraded if the hidden form's timer process is short running and is running infrequently.
In a nutshell, this is the solution. Let's move from the theoretical realm to the practical realm.
Mapping the Issues to the Alarm Solution
We will create a hidden form with an OnTimer
function that will monitor a specific table. The OnTimer
will run infrequently, like every 15 seconds, and when monitoring a special table, it will do as little work as possible as to not disturb the rest of the VBA application.
The .NET DLL will be attached statically to the VBA solution (discussed in the section "Running on a different machine"), and as such, it is available at the beckon call of the VBA code.
The construction of the DLL is not difficult. Also, letting the client machine know of the DLL that is to be visible to the VBA code in MS Access is not too difficult.
We are now home free.
Writing the C# Alarm DLL
.NET allows us to write a DLL that will be COM visible; MS Office applications interact with COM classes, not .NET classes. In order to compile the project and have the COM Visible bit set, we need to run VS as an Administrator on Windows Vista and Windows 7 in addition to logging in with an Administrator account (Windows XP requires only that you log in as an Administrator). For that purpose, right-click on the VS icon or VS menu item, and select the "Run as administrator" option off the right-click driven menu.
Creating the Alarm DLL
Fire up VS (I am using VS2010 beta version), and then choose the Class Library template.
Now, we need an interface that will become the COM interface. For that purpose, you will need to include a "using
" construct:
using System.Runtime.InteropServices;
Your interface should look something like this:
[ComVisible(true)]
public interface IAlarm
{
void PlaySound();
void PlayStop();
}
The interface exposes two functions: "PlaySound
" and "PlayStop
". The second name seems strange: "PlayStop
". Are you kidding me? Originally, I wanted to call the two functions "Play
" and "Stop
". Alas, VB has a construct "Stop
" that trumps an external "Stop
" function. Hence: "PlaySound
" and "PlayStop
".
Sound Effects
An alarm needs to blare some sort of a sound. Some sites will provide charge-free MP3, wav, etc., sound files. For my real life app, I recommended a screaming girl's sound, which was swiftly rejected. So I will provide this sound effect in this example. Neither my wife nor my dog liked the sound, which means that if you dislike the alarm sound badly enough, then you will attend to whatever needs attending faster. I downloaded the free of charge screaming girl sound off the following site: http://www.partnersinrhyme.com/soundfx/ PDsoundfx/PDsoundfx_sounds/screams_sounds/screams_scream_wav.shtml and embedded the sound in the Resources section of the project-properties.
The Alarm Class
The Alarm
class itself is uneventful. It inherits from the previously created IAlarm
interface, which ensures that it implements the PlaySound()
and PlayStop()
functions. It has a member SoundPlayer
private variable called _player
:
private SoundPlayer _player;
SoundPlayer
is a class that is part of the System.Media
namespace, that can play Wav files. Therefore, if the sound file that you downloaded is not a Wav file, then you will need to convert it to a Wav file. There is a multitude of free sound converter options available to you. You may checkout CDex on www.filehippo.com, or the AVC converter on http://www.any-video-converter.com, and much more.
A word of caution: if you would like to have multiple sound files string together in a sequence to be heard sequentially, my humble advice is that you string them together outside the Alarm program in a single Wav file, as opposed to having the Alarm program play them in a train of Wav sound clips.
The constructor of Alarm
consists of:
// Initialize the _player
_player = new SoundPlayer();
// Set the _player stream location
_player.Stream = Resources.Alarm;
// Load the _player
_player.Load();
The AlarmCS
class implements the PlaySound()
and PlayStop()
functions:
public void PlaySound()
{
_player.PlayLooping();
}
public void PlayStop()
{
_player.Stop();
}
The _player.PlayLooping()
, when called, will run continually in a loop. This is the long running function for which .NEt was so badly needed.
Lastly, the AlarmCS
is decorated as so:
[ComVisible(true)]
[ClassInterface(ClassInterfaceType.None)]
Compile, and we are done!!!
Signing the Application
In order to run in a different machine, it is best that the DLL be signed. My recommendation is that your company employs a single key identifying itself. However, for development, you may employ a different key. You will find the signing capabilities in the signing portion of the project-properties:
Running on a Different Machine
Running on the same machine that you compiled on is a no brainer. VS registers the COM classes for you. However, what about running the DLL you created on a different machine?
The COM DLL needs to be registered. COM registration means that the DLL needs to be represented in the system registry. Thereafter, the DLL is visible globally to the entire system. For more information about the representation in the Registry, see: http://msdn.microsoft.com/en-us/library/h627s4zy.aspx.
In a cmd window that you start using "Running as administrator", we will issue the following command:
regasm AlarmCS.DLL /codebase /tlb:AlarmCS.TLB
on the target machine (that has .NET installed but no VS installed). So, for example, regasm.exe can be found, on my machine, in C:\Windows\Microsoft.NET\Framework\v2.0.50727 and also in C:\Windows\Microsoft.NET\Framework64\v4.0.21006 and a few other places. Run Regasm that suits your MS Access, the 32 bits or 64 bits version.
Alternatively, if you have Windows SDK installed, then you may use the Tlbexp.exe utility to create a .tlb file. Again, use the correct Tlbexp.exe for your version of MS Office, 32 bit or 64 bit as appropriate.
Another account on making an assembly COM visible can be found in the post: "Making a .NET DLL COM-Visible", see: http://jumbloid.blogspot.com/2009/12/making-net-dll-com-visible.html.
Also, Appendix C of Access 2007 VBA Programmer's Reference (Programmer to Programmer) by Teresa Hennig, Rob Cooper, Geoffrey Griffith, and Armen Stein (Paperback - May 14, 20.07) has a good account of making a .NET assembly COM-Visible.
MS Access VBA Code
The code in here is not meant to be production code, but rather an example. As such, simplification was the primary directive, not functionality nor robustness.
The Access application is very, very simple. It contains one table and two columns. The purpose of this example is to simulate internal events; when one or more events are true, then the alarm should sound. When none of the events is true, then the alarm should stop. The table named "Table1" consists of two columns: "ID" an AutoNumber column, and "SoundAlarm", a True/False column.
In real life, we would probably provide an alarm on/off global flag, a snooze on/off global flag, etc., which means that we need a more sophisticated set of rules to handle all of these. But for us right now, this simple rule will do.
The first order of the day is to reference the DLL we built. Within the VBA code (Alt-F11) from the "Tools" menu, select "References...", and the system will respond with the following dialog:
Select the "Browse..." button and open the .tlb file you created with the Regasm utility.
Now, you will need two forms, the first contains the table (for which a sub form will be created). The second is the hidden form carrying the OnTimer
routine, which looks as follows:
' This function handler will handle the case where
' internal processing turn alarm events on/off
Private Sub Form_Timer()
Dim events As Long
' How many events do we have needing an alarm
events = modAlarm.NumberOfTriggerEvents
' If there are none then turn the alarm off!!
If events = 0 Then
modAlarm.TurnAlarmOff
Exit Sub
End If
' If alarm is running do not restart the sound
If modAlarm.IsAlarmOn Then Exit Sub
' Alarm is not running turn it on
modAlarm.TurnAlarmOn
End Sub
The OnLoad
method of the Alarm form is:
Private Sub Form_Load()
DoCmd.OpenForm "HiddenForm", acNormal, WindowMode:=acHidden
End Sub
A production application is more than likely to employ a startup routine that will perform some upfront work. This startup routine will likely be the place where the hidden form "HiddenForm
" will be loaded.
The library of supporting routines is in a VBA module, "modAlarm
", as follows:
Option Compare Database
Option Explicit
' Alarm itself
Private alarm As AlarmCS.AlarmCS
' State of Alarm
Private alarmOn As Boolean
' Initialization of module
Public Sub AlarmInit()
Set alarm = New AlarmCS.AlarmCS
alarmOn = False
End Sub
' Read only view to the world of the alarmOn state
Public Property Get IsAlarmOn() As Boolean
IsAlarmOn = alarmOn
End Property
' A function returning the number of events needing alarm
Public Function NumberOfTriggerEvents() As Long
Dim sql As String, rc As Boolean, rs As ADODB.Recordset
Dim cmnd As ADODB.Command
sql = "SELECT COUNT(*) FROM [Table1] WHERE SoundAlarm"
Set cmnd = New ADODB.Command
With cmnd
.ActiveConnection = CurrentProject.Connection
.CommandText = sql
.CommandType = adCmdText
Set rs = .Execute
End With
If rs Is Nothing Then
NumberOfTriggerEvents = 0
ElseIf rs.EOF Then
NumberOfTriggerEvents = 0
ElseIf rs(0) = 0 Then
NumberOfTriggerEvents = 0
Else
NumberOfTriggerEvents = rs(0)
End If
End Function
' Turn alarm on/off depending on event count
Public Sub TurnAlarmOnOff()
Dim events As Long
' Check for event needing alarm count
events = NumberOfTriggerEvents()
' Turn alarm on if count is greater than 0
' Turn alarm off otherwise
If events > 0 Then
' if alarm is already running do not return it on
If alarmOn Then Exit Sub
TurnAlarmOn
Else
TurnAlarmOff
End If
End Sub
' Turn alarm on unconditionally
Public Sub TurnAlarmOn()
On Error GoTo TurnAlarmOnErr
alarm.PlaySound
alarmOn = True
Exit Sub
TurnAlarmOnErr:
' Probably needs to run due to debugging stop/start
If Err.Number = 91 Then
AlarmInit
Exit Sub
End If
' Not a good idea to publish function names,
' but this is an instructional
' software as opposed to production software
MsgBox Err.Description, vbOKOnly, "TurnAlarmOn [" & _
Err.Number & "]"
End Sub
' Turn alarm off unconditionally
Public Sub TurnAlarmOff()
On Error GoTo TurnAlarmOffErr
alarm.PlayStop
alarmOn = False
Exit Sub
TurnAlarmOffErr:
' Probably needs to run due to debugging stop/start
If Err.Number = 91 Then
AlarmInit
Exit Sub
End If
' Not a good idea to publish function names,
' but this is an instructional
' software as opposed to production software
MsgBox Err.Description, vbOKOnly, "TurnAlarmOff [" & _
Err.Number & "]"
End Sub
Conclusion
I have shown the steps to create a reference .NET DLL to be accessed from MS Access for the purposes of processing a long-running process. A second possibility is to write an add-on routine. See Appendix C of Access 2007 VBA Programmer's Reference (Programmer to Programmer) by Teresa Hennig, Rob Cooper, Geoffrey Griffith, and Armen Stein (Paperback - May 14, 20.07) in order to accomplish the add-in .NET routine.
The .NET development can be done using any of the VS versions; however, you should use the lowest MS Access version that your customers will be using.
Enjoy!