[Rd] Patching "update.packages" to enable updating of only a user defined subset of packages

Tal Galili tal.galili at gmail.com
Mon Apr 18 08:51:04 CEST 2011


Hello dear R developers,

I recently found out that it is not possible to limit update.packages() to
update only a few packages at a time.

The patch offered simply adds a 'subset' parameter and the statement bounded
within "if(!missing(subset))" to implement it.
The code is pasted bellow (and also attached as an .r file).

Might this patch be considered valuable to be added to R?


(in the code bellow I called the function "update.packages.2" so to not mask
the original update.packages)


With much respect,
Tal

###############################


update.packages.2 <-
function (lib.loc = NULL, repos = getOption("repos"), contriburl =
contrib.url(repos,
    type), method, instlib = NULL, ask = TRUE, available = NULL,
    oldPkgs = NULL, ..., checkBuilt = FALSE, type = getOption("pkgType"),
subset)
{
    force(ask)
    text.select <- function(old) {
        update <- NULL
        for (k in seq_len(nrow(old))) {
            cat(old[k, "Package"], ":\n", "Version", old[k, "Installed"],
                "installed in", old[k, "LibPath"], if (checkBuilt)
                  paste("built under R", old[k, "Built"]), "\n",
                "Version", old[k, "ReposVer"], "available at",
                simplifyRepos(old[k, "Repository"], type))
            cat("\n")
            answer <- substr(readline("Update (y/N/c)?  "), 1L,
                1L)
            if (answer == "c" | answer == "C") {
                cat("cancelled by user\n")
                return(invisible())
            }
            if (answer == "y" | answer == "Y")
                update <- rbind(update, old[k, ])
        }
        update
    }
    if (is.null(lib.loc))
        lib.loc <- .libPaths()
    if (is.null(available))
        available <- available.packages(contriburl = contriburl,
            method = method)
    if (is.null(oldPkgs)) {
        oldPkgs <- old.packages(lib.loc = lib.loc, contriburl = contriburl,
            method = method, available = available, checkBuilt = checkBuilt)
        if (is.null(oldPkgs))
            return(invisible())
    }
    else if (!(is.matrix(oldPkgs) && is.character(oldPkgs)))
        stop("invalid 'oldPkgs'; must be a result from old.packages()")
 if(!missing(subset)) # if the user uses 'subset'
 {
if(mode(subset) != "character") stop("'subset' must be a character vector
(with names of packages)")
 ss <- oldPkgs[,"Package"] %in% subset # are there any old packages that the
user would have liked to update?
 if(!any(ss)) {
cat("There are no available new updates for the packages you have entered \n
")
 return(invisible())
} # if not - then we can end the function here
 oldPkgs <- oldPkgs[ss,] # else - we can go on, but this time only use a
subset of the oldPkgs.
 if(sum(ss)==1) oldPkgs <- t(oldPkgs) # in case there is only 1 package to
update, make sure the object "oldPkgs" is of the correct form (6 columns
instead of 1 vector)
 }
    update <- if (is.character(ask) && ask == "graphics") {
        if (.Platform$OS.type == "windows" || .Platform$GUI ==
            "AQUA" || (capabilities("tcltk") && capabilities("X11"))) {
            k <- select.list(oldPkgs[, 1L], oldPkgs[, 1L], multiple = TRUE,
                title = "Packages to be updated", graphics = TRUE)
            oldPkgs[match(k, oldPkgs[, 1L]), , drop = FALSE]
        }
        else text.select(oldPkgs)
    }
    else if (isTRUE(ask))
        text.select(oldPkgs)
    else oldPkgs
    if (length(update)) {
        if (is.null(instlib))
            instlib <- update[, "LibPath"]
        libs <- unique(instlib)
        for (l in libs) install.packages(update[instlib == l,
            "Package"], l, contriburl = contriburl, method = method,
            available = available, ..., type = type)
    }
}

# Example:
# old.packages()
# update.packages.2(subset = "MASS")








----------------Contact
Details:-------------------------------------------------------
Contact me: Tal.Galili at gmail.com |  972-52-7275845
Read me: www.talgalili.com (Hebrew) | www.biostatistics.co.il (Hebrew) |
www.r-statistics.com (English)
----------------------------------------------------------------------------------------------


More information about the R-devel mailing list