[R-gui] Not a bug in Rcmdr, GUI for require(package)?

John Fox jfox at mcmaster.ca
Fri Jul 16 01:10:35 CEST 2004


Dear James,

I've written the following .onLoad() function for the Rcmdr package, which
will install missing packages from CRAN, Bioconductor, or a local package
directory. One deficiency is that the package directory must (like CRAN)
have a PACKAGES file, but this should cover the case of a CD, where such a
file could be included.

Regards,
 John

.onLoad <- function(...){
    save.options <- options(warn=-1)
    on.exit(options(save.options))
    lattice <- require(lattice)
    foreign <- require(foreign)
    tcltk <- require(tcltk)
    abind <- require(abind)
    lmtest <- require(lmtest)
    multcomp <- require(multcomp)
    mvtnorm <- require(mvtnorm)
    relimp <- require(relimp)
    effects <- require(effects)
    rgl <- require(rgl)
    mgcv <- require(mgcv)
    car <- require(car)
    if (!tcltk) stop("The tcltk package is absent. The Rcmdr cannot
function.")
    absent <- !c(lattice, foreign, abind, lmtest, multcomp, mvtnorm, relimp,
        effects, rgl, mgcv, car)
    missing.packages <- c("lattice", "foreign", "abind", "lmtest",
"multcomp", 
                    "mvtnorm", "relimp", "effects", "rgl", "mgcv",
"car")[absent]
    if (any(absent)) {
        response <- tkmessageBox(message=paste("The following packages
required by Rcmdr are missing:\n",
                            paste(missing.packages, collapse=", "),
"\nInstall these packages?"), 
                        icon="error", type="yesno")
        if (as.character(response) == "yes") {
            top <- tktoplevel(borderwidth=10)
            tkwm.title(top, "Install Missing Packages")
            locationFrame <- tkframe(top)
            locationVariable <- tclVar("CRAN")
            CRANbutton <- tkradiobutton(locationFrame,
variable=locationVariable, value="CRAN")
            BioconductorButton <- tkradiobutton(locationFrame,
variable=locationVariable, value="Bioconductor")
            localButton <- tkradiobutton(locationFrame,
variable=locationVariable, value="local")
            directoryVariable <- tclVar("")
            directoryFrame <- tkframe(locationFrame)
            onBrowse <- function(){
                tclvalue(directoryVariable) <- tclvalue(tkchooseDirectory())
                }
            browseButton <- tkbutton(directoryFrame, text="Browse",
width="12", command=onBrowse, borderwidth=3)
            locationField <- tkentry(directoryFrame, width="20",
textvariable=directoryVariable)
            locationScroll <- tkscrollbar(directoryFrame,
orient="horizontal",
                repeatinterval=5, command=function(...)
tkxview(locationField, ...))
            tkconfigure(locationField, xscrollcommand=function(...)
tkset(locationScroll, ...))
            tkgrid(tklabel(top, text="Install Packages From:", fg="blue"),
sticky="nw")
            tkgrid(tklabel(directoryFrame, text="Specify package
\ndirectory:", justify="left"), 
                locationField, sticky="w")
            tkgrid(browseButton, locationScroll, sticky="w")
            tkgrid(locationScroll, sticky="ew")
            tkgrid(tklabel(locationFrame, text="CRAN"), CRANbutton,
sticky="w")
            tkgrid(tklabel(locationFrame, text="Bioconductor"),
BioconductorButton, sticky="w")
            tkgrid(tklabel(locationFrame, text="Local package
directory\n(must include PACKAGES index file)", 
                justify="left"), localButton, directoryFrame, sticky="nw")
            tkgrid(locationFrame, sticky="w")
            tkgrid(tklabel(top, text=""))
            onOK <- function(){
                errorMessage <- function() tkmessageBox(message=paste(
                    "The following packages were not found at the specified
location:\n",
                    paste(missing.packages[!present], collapse=", ")),
icon="error", type="ok")
                tkgrab.release(top)
                tkdestroy(top)
                location <- tclvalue(locationVariable)
                if (location == "CRAN") {
                    packages <- CRAN.packages()[,1]
                    present <- missing.packages %in% packages
                    if (!all(present)){
                        errorMessage()
                        stop("Missing packages.", call.=FALSE)
                        }
                    install.packages(missing.packages, lib=.libPaths()[1])
                    }
                else if (location == "Bioconductor") {
                    packages <- CRAN.packages(CRAN=getOption("BIOC"))[,1]
                    present <- missing.packages %in% packages
                    if (!all(present)){
                        errorMessage()
                        stop("Missing packages.", call.=FALSE)
                        }
                    install.packages(missing.packages., lib=.libPaths()[1],
                        CRAN=getOption("BIOC"))
                    }
                else {
                    directory <- paste("file:", tclvalue(directoryVariable),
sep="")
                    packages <- CRAN.packages(contriburl=directory)[,1]
                    present <- missing.packages %in% packages
                    if (!all(present)){
                        errorMessage()
                        stop("Missing packages.", call.=FALSE)
                        }
                    install.packages(missing.packages, contriburl=directory,
lib=.libPaths()[1])
                    }
                for (package in missing.packages) require(package,
character.only=TRUE)
                }
            onCancel <- function(){
                tkgrab.release(top)
                tkdestroy(top)
                stop("Missing packages.", call.=FALSE)
                }
            onHelp <- function() help("install.packages")
            buttonsFrame <- tkframe(top)
            OKbutton <- tkbutton(buttonsFrame, text="OK", fg="darkgreen",
width="12", command=onOK, default="active",
                    borderwidth=3)
            cancelButton <- tkbutton(buttonsFrame, text="Cancel", fg="red",
width="12", command=onCancel,
                    borderwidth=3)
            helpButton <- tkbutton(buttonsFrame, text="Help", width="12",
command=onHelp, borderwidth=3)
            tkgrid(OKbutton, tklabel(buttonsFrame, text="  "), cancelButton,
tklabel(buttonsFrame, text="            "), 
                helpButton, sticky="w")
            tkgrid(buttonsFrame, sticky="w")
            for (row in 0:2) tkgrid.rowconfigure(top, row, weight=0)
            tkgrid.columnconfigure(top, 0, weight=0)
            .Tcl("update idletasks")
            tkwm.resizable(top, 0, 0)
            tkbind(top, "<Return>", onOK)
            tkwm.deiconify(top)
            tkgrab.set(top)
            tkfocus(top)
            tkwait.window(top)
            }
        else stop("Missing packages: ", paste(missing.packages, collapse=",
"), call.=FALSE)
        }           
    }

> -----Original Message-----
> From: r-sig-gui-bounces at stat.math.ethz.ch 
> [mailto:r-sig-gui-bounces at stat.math.ethz.ch] On Behalf Of 
> James Wettenhall
> Sent: Wednesday, July 14, 2004 7:09 PM
> To: John Fox
> Cc: 'Feng, Yang [Ontario]'; r-sig-gui at stat.math.ethz.ch
> Subject: RE: [R-gui] Not a bug in Rcmdr, GUI for require(package)?
> 
> Hi John,
> 
> On Wed, 14 Jul 2004, John Fox wrote:
> > implement it in a cross-platform manner. I don't know how 
> to do that 
> > via tcltk or I'd offer to do it.
> 
> I think I know how to do it via Tcl/Tk, but if using Windows 
> with the GraphApp Rgui running (even in SDI), there are 
> likely to be some annoying focus-stealing problems between 
> GraphApp and Tcl/Tk because of some of the GraphApp widgets 
> that pop-up (e.g. progress bar) when you install a package.
> 
> > On the other hand, if a user doesn't have an active Internet 
> > connection, how likely is it that he or she will be able to install 
> > missing packages?
> 
> Very likely for our workshops.  Many I.T. departments are 
> becoming more strict about not letting outsiders connect up 
> their laptops to the local network because of fears of 
> viruses and trojans.  So if we present a microarray workshop 
> at a conference where people bring their own laptops, we 
> provide a CD containing all of the necessary R packages for 
> participants who have failed to install the correct software 
> beforehand.
> 
> Regards,
> James
> 
> _______________________________________________
> R-SIG-GUI mailing list
> R-SIG-GUI at stat.math.ethz.ch
> https://www.stat.math.ethz.ch/mailman/listinfo/r-sig-gui



More information about the R-SIG-GUI mailing list