[Rd] Using macros
John Fox
jfox at mcmaster.ca
Wed Jun 9 01:10:54 CEST 2004
Dear list members,
I've been puzzling over how best to clean up the code for my Rcmdr package.
In particular, there's a lot of repetitive tcltk code in the package, and as
Martin Mächler has pointed out to me, this makes the package difficult to
maintain.
If R were Lisp, I'd use macros for much of the clean up. My efforts to do
similar things with R functions has run into problems with scoping issues.
My attempts to solve these problems have worked, but lead to awkward code
(perhaps because I've not been clever enough to do it in a natural way).
Thomas Lumley describes a function for constructing R "macros" in the Sept.
2001 issue of R-news. Here's an application to producing standard OK,
Cancel, and Help buttons using tcltk:
### Thomas's defmacro:
defmacro <- function(..., expr){
expr <- substitute(expr)
a <- substitute(list(...))[-1]
## process the argument list
nn <- names(a)
if (is.null(nn)) nn <- rep("", length(a))
for (i in seq(length=length(a))){
if (nn[i] == "") {
nn[i] <- paste(a[[i]])
msg <- paste(a[[i]], "not supplied")
a[[i]] <- substitute(stop(foo), list(foo = msg))
}
}
names(a) <- nn
a <- as.list(a)
ff <- eval(substitute(
function(){
tmp <- substitute(body)
eval(tmp, parent.frame())
},
list(body = expr)))
## add the argument list
formals(ff) <- a
## create a fake source attribute
mm <- match.call()
mm$expr <- NULL
mm[[1]] <- as.name("macro")
attr(ff, "source") <- c(deparse(mm), deparse(expr))
## return the macro
ff
}
OKCancelHelp <- defmacro(window=top, OKbutton=OKbutton, onOK=onOK,
cancelButton=cancelButton, onCancel=onCancel,
helpButton=helpButton, onHelp=onHelp, helpSubject,
expr={
OKbutton <- tkbutton(window, text="OK", fg="darkgreen",
width="12", command=onOK, default="active")
onCancel <- function() {
tkdestroy(top)
}
cancelButton <- tkbutton(window, text="Cancel", fg="red",
width="12", command=onCancel)
onHelp <- function() {
help(helpSubject)
}
helpButton <- tkbutton(window, text="Help", width="12",
command=onHelp)
}
)
test <- function(){
top <- tktoplevel()
onOK <- function(){
tkmessageBox(message="Foo.", icon="info", type="ok")
tkdestroy(top)
}
OKCancelHelp(helpSubject="lm")
tkgrid(OKbutton, cancelButton, helpButton)
}
test()
That is, the OKCancelHelp macro makes the buttons and the call-back
functions onCancel and onHelp in the environment of the calling function
(here test). This seems to work fine, but I wonder whether there are any
hidden pitfalls to adopting this as a general strategy. For example, is
there some problematic interaction with namespaces if I export the macro
OKCancelHelp?
Any advice would be appreciated.
John
--------------------------------
John Fox
Department of Sociology
McMaster University
Hamilton, Ontario
Canada L8S 4M4
905-525-9140x23604
http://socserv.mcmaster.ca/jfox
More information about the R-devel
mailing list