This is a brief introduction to using S functions and objects as event
handlers in COM. Our example is intentionally simple and doesn't do
much other than illustrate the mechanism. We will register a
collection of S functions as event handlers for the top-level Excel
application object. This singals events such as when a sheet is made
active and inactive, when the selection changes, when a new workbook
is created, when the window is resized and so on.
We start by determining what events we should implement. We do this
by knowing that the interface of interest is the
Application in the Excel type library.
So the first thing we do is to load the
SWinTypeLibs
and read the type library for Excel into memory.
library(SWinTypeLibs)
lib = LoadTypeLib("C:\\Program Files\\Microsoft Office\\Office\\EXCEL9.OLB")
For those who want to see only the user-level mechanism,
jump to here.
Now, we can ask about the
Application.
lib[["Application"]]
We see that this is a CoClass type which essentially means that it is
a container for multiple interfaces and classes. So we need to look at
each of its elements.
getElements(lib[["Application"]])
This returns a list with two elements, one for the
_Application and another for the
IAppEvents. This is the one we want. From
this, we can ask for all of the event methods, i.e. the ones to which
we have to respond as called by the event source, the Excel
Application object.
i = getElements(lib[["Application"]])[[2]]
funcs = getFuncs(i)
The names of the functions are given
names(funcs)
> names(ff[[2]])
[1] "QueryInterface" "AddRef" "Release"
[4] "GetTypeInfoCount" "GetTypeInfo" "GetIDsOfNames"
[7] "Invoke" "NewWorkbook" "SheetSelectionChange"
[10] "SheetBeforeDoubleClick" "SheetBeforeRightClick" "SheetActivate"
[13] "SheetDeactivate" "SheetCalculate" "SheetChange"
[16] "WorkbookOpen" "WorkbookActivate" "WorkbookDeactivate"
[19] "WorkbookBeforeClose" "WorkbookBeforeSave" "WorkbookBeforePrint"
[22] "WorkbookNewSheet" "WorkbookAddinInstall" "WorkbookAddinUninstall"
[25] "WindowResize" "WindowActivate" "WindowDeactivate"
[28] "SheetFollowHyperlink"
>
The first 7 of these come from the IDispatch interface and we can
ignore.
funcs = funcs[-c(1:7)]
In order to respond to these Excel events, we will create S functions
corresponding to the different event types. When an event is
generated in Excel, the corresponding function will be invoked in S.
To do this, we will create a regular COM server in S by supplying a
list of function objects. So our task is to define this
list of functions.
Since we may not want to actually provide a function for each event
method in this interface, we might think about creating default
handlers for those functions we won't implement. We have all the
information in the
funcs to do this since we have the
function name, the parameters, etc. Since these functions are for
events, they do not return anything. Accordingly, all we really need
is the function name and a degenerate function that takes any number
of arguments and does nothing.
methods = vector("list", length(funcs))
methods[1:length(methods)] = list(function(...){})
names(methods) = names(funcs)
Now, we can provide the methods we do want to implement and insert
them into this list. In our example, we will catch the events named
SheetActivate, NewWorkbook and SheetSelectionChange.
For our example, we will do very little in these functions except for
write a message to the terminal.
methods[["SheetActivate"]] = function(sheet) {
cat("In sheet activate\n")
}
For the new book event, we will find out how
many books exist in this collection.
methods[["NewWorkbook"]] = function(book) {
n = book[["Parent"]][["Workbooks"]][["Count"]]
cat("In New workbook: # books", n, "\n")
}
And finally, the SheetSelectionChange handler
is defined as
methods[["SheetSelectionChange"]] =
function(sheet, range) {
cat("Sheet selection changed\n")
}
Note that we have two arguments here and that we are given the (newly)
selected range. We might use this for example to update a plot in
GGobi by brushing or identifying the selected records.
At this point, we have our list of methods for the S-language COM
server. In the usual server, we also need to specify a mechanism for
mapping method and parameter names to integers and back so that
clients of this server can use the Invoke method of the IDispatch
interface in COM. However, we are in a different situation here. We
are implementing an interface that the event source has already
defined. Since the event source is the one that is calling our
methods, it doesn't need to ask how to map names to integers; it has
already done this. It will call Invoke directly without first calling
the GetNamesOfIDs method of the server. It will call Invoke with the
IDs it uses. We must therefore figure out how to map these numbers to
the event method names. Again, the type library will help us do this.
We can find the IDs for the different method names
using the following simple function
getEventNameIDs =
function(info)
{
tmp = names(getFuncs(info))
el = sapply(tmp, function(x) getNameIDs(x, info))
names(el) = tmp
el
}
This expects to be called with the
ITypeLibEntry object
representing the
IAppEvent in our case. It
computes all the functions and iterates over their names to get the
corresponding identifier.
Note that we could create an instance of the Excel Application class
using the
RDCOMClient and then ask about its
type information. Unfortunately, since that is an object and
implements the IDispatch interface, we get the type information
specific to that interface and not the general
Application CoClass.
The next step in our preparation is to create our COM object that will
act as the event handler. This will be the
sink
for the event source. We have a list of functions that we want to use
as the methods for the
IAppEvents
interface. We also have the mapping of the names of the methods to the
integers that will be used by the event source when invoking the
different methods. To create a COM server in S we need to provide a
mechanism for dispatching the invocation from the event source to the
particular S function. We do this by providing another S function
that has access to the methods and the name-identifier map. This
function processes the Invoke call from the IDispatch interface and
interprets with respect to the available methods. The following
function does this. It returns a function thus creating a closure
with an environment that contains the methods (
funcs)
and the name-identifer map (
ids). The function it
returns (
invoke) takes 4 arguments: the identifier of
the method being invoked, a logical vector indicating the style of
invocation (e.g. regular function or property accessor), the arguments
to the call, and the identifiers of the names of the arguments. Since
we know that events are called with their full collection of
arguments, we don't need to worry about the final arguments.
The
invoke function is quite simple. It
retrieves the name of the method from the name-identifier map.
Then it searches the list of functions for an entry with that name.
If such an element exists, it calls it with the specified
arguments (which are given in reverse order by COM).
createCOMEventServer = function(funcs, ids) {
invoke =
function(id, method, args, namedArgs) {
funcName = names(ids)[which(ids == id)]
if(length(funcName)) {
eval(as.call(c(funcs[[funcName]], rev(args))), env = globalenv())
} else {
cat("Ignoring event number", id, "\n")
}
}
list(Invoke = invoke, GetNamesOfIDs = NULL)
}
Note that we return a list of two functions, the first being the
invoke function and the second which will never be
used in this case since the Excel event source will never ask for an
identifier for a name.
We should also note here that we have separately created a list of
functions for all of the methods in the interface we have to implement
and then created a dispatch mechanism that calls these methods even if
they are degenerate. Our dispatch mechanism however gracefully
handles the case where there is no function for a particular method.
So we could just as easily have provided a list of only the methods of
interest. Either works, but the reduced list is marginally more
efficient since it avoids calls to empty functions.
ids = getEventNameIDs(lib[["IAppEvents"]])
Given this function, we can create our server. We first load the
RDCOMServer. Then we create our dispatch
mechanism by calling
createCOMEventServer. And
finally we create the C++-level COM object that can be used with
clients and event sources everywhere by calling
R_RCOMSObject.
library(RDCOMServer)
server = createCOMEventServer(methods, ids)
server = .Call("R_RCOMSObject", server)
Now we are ready to create the Excel application instance which we do
in the usual manner using
COMCreate in the
RDCOMClient package.
library(RDCOMClient)
e = COMCreate("Excel.Application")
For the purposes of this demonstration, we will create a workbook
before we register to handle any events. This will ensure that the
only events we get initially are ones that we manually generated by
interacting with the Excel GUI. Later, we'll see how
book = e[["Workbooks"]]$Add()
e[["Visible"]] = TRUE
At this point, we are finally ready to make the connection between the
event source (Excel) and our event handler. We ask for the connection
points and extract the first and only element.
Then we call the
connectConnectionPoint
connPoint = getConnectionPoints(e)[[1]]
cookie = connectConnectionPoint(connPoint, server)
Now move the mouse over to Excel and start switching between the
different sheets and selecting different cells and ranges. You should
notice output being generated in the R console informing you of what
events have been processed by our handler.
Note that we can continue to control Excel
using regular COM calls and some of these might
generate events.
e[["Workbooks"]]$Add()
In this case, our handlers will be invoked
within our (client) COM call.
And finally we disconnect the event handler from
Excel and we no longer receive events.
disconnectConnectionPoint(connPoint, cookie)
The developer will typically know which object they want to
receive events from. For example, she might be interested in
the Excel Workbook. We can get the possible connection
points directly from an instance of this object
using
e = COMCreate("Excel.Application")
book = e[["Workbooks"]]$Add()
connections = getConnectionPoints(book)
Now, from this list of possible connection interfaces, we can
find the definitions of these interfaces from the ITypeLibrary.
For the Workbook, there is only one possible interface.
We can find the associated ITypeInfo from the library
iface = lib[[names(connections)]]
From this, we can generate a template event handler
that can be used with the connection point.
s = createCOMEventServerInfo(iface, complete = TRUE)
We can then examine the different methods and provide
implementations for the ones of interest.
methods = list(...)
s = createCOMEventServer(iface, methods = methods)
Now we have sufficient information in R to
construct an event handler
and we can do this with the
createCOMEeventServer
function
server = createCOMEventServer(s$methods, s$ids, direct = TRUE, verbose = TRUE)
This creates the S COM dispatcher and the associated C level
server (via the
direct argument).
We register the server with the connection point in the same way as before
e = COMCreate("Excel.Application")
book = e[["Workbooks"]]$Add()
e[["Visible"]] = TRUE
connPoint = getConnectionPoints(book)[[1]]
cookie = connectConnectionPoint(connPoint, server)