Determine minimum R version for all package dependencies

僤鯓⒐⒋嵵緔 提交于 2019-12-04 03:24:25

问题


I am a package developer and want to state the minimum R version required to use my package in the DESCRIPTION file.

available.packages parses DESCRIPTIONS of packages, but the result is not (easily) machine readable to lookup recursive dependencies, since the Imports and Depends fields are comma separated text, and sometimes contain packages have version requirements.

The solution described in: Listing R Package Dependencies Without Installing Packages is not a recursive solution. If a nested dependency needed R > 3.3, I want to know about it.

At a minimum, I would like to see the minimum version of R and imported, linked, and depends packages for a given CRAN package. Better still would be to list the package or packages which set the minimum R or package version.

By eliminating dependencies which have higher version requirements, I can serve more people with institutionally old R versions they can't fix: some are still on R 2.x.


回答1:


min_r_version <- function(package="ggplot2", exclude_main_pkg=TRUE) {

  purrr::walk(c("tools", "purrr", "devtools", "stringi", "tidyr", "dplyr"), 
              require, character.only=TRUE)

  deps <- package_dependencies(package, recursive=TRUE)

  if (exclude_main_pkg) {
    pkgs <- deps[[1]]
  } else {
    pkgs <- c(package, deps[[1]])
  }

  available.packages() %>% 
    as_data_frame() %>% 
    filter(Package %in% pkgs) %>% 
    select(Depends)  %>% 
    unlist() -> pkg_list

  # if main pkg only relied on core R packages (i.e. pkgs that aren't in CRAN) and we 
  # excluded the pkg itself from the min version calculation, this is an edge case we need
  # to handle.

  if (length(pkg_list) == 0) return("Unspecified")

  stri_split_regex(pkg_list, "[,]") %>%
    unlist() %>%
    trimws() %>%
    stri_match_all_regex(c("^R$|^R \\(.*\\)$")) %>%
    unlist() %>%
    discard(is.na(.)) %>%
    unique() %>%
    stri_replace_all_regex("[R >=\\(\\)]", "") %>%
    data_frame(vs=.) %>%
    separate(vs, c("a", "b", "c"), fill="right") %>%
    mutate(c=ifelse(is.na(c), 0, c)) %>%
    arrange(a, b, c) %>%
    tail(1) %>%
    unite(min, a:c, sep=".") -> vs

  return(vs$min)

}

# did we handle the edge cases well enought?
base <- c("base", "compiler", "datasets", "grDevices", "graphics", "grid", "methods", "parallel", "profile", "splines", "stats", "stats4", "tcltk", "tools", "translations")
(base_reqs <- purrr::map_chr(base, min_r_version))
##  [1] "Unspecified" "Unspecified" "Unspecified" "Unspecified" "Unspecified"
##  [6] "Unspecified" "Unspecified" "Unspecified" "Unspecified" "Unspecified"
## [11] "Unspecified" "Unspecified" "Unspecified" "Unspecified" "Unspecified"

# a few of the "core" contributed pkgs rely on a pkg or two outside of base
# but many only rely on base packages, to this is another gd edge case to
# text for.
contrib <- c("KernSmooth", "MASS", "Matrix", "boot", "class", "cluster", "codetools", "foreign", "lattice", "mgcv", "nlme", "nnet", "rpart", "spatial", "survival")
contrib_reqs <- purrr::map_chr(contrib, min_r_version)
##  [1] "Unspecified" "Unspecified" "3.0.0"       "Unspecified" "3.1.0"      
##  [6] "Unspecified" "Unspecified" "Unspecified" "Unspecified" "3.0.2"      
## [11] "3.0.0"       "Unspecified" "Unspecified" "Unspecified" "3.0.1"      

# See what the min version of R shld be for some of my pkgs
min_r_version("ggalt") # I claim R (>= 3.0.0) in DESCRIPTION
## [1] "3.1.2"

min_r_version("curlconverter") # I claim R (>= 3.0.0) in DESCRIPTION
## [1] "3.1.2"

min_r_version("iptools") # I claim R (>= 3.0.0) in DESCRIPTION
## [1] "3.0.0"



回答2:


Based on ideas from @hrbrmstr and written with base functions, I'm now using the following function:

min_r_version <- function(pkg) {
  requireNamespace("tools")
  requireNamespace("utils")
  avail <- utils::available.packages(utils::contrib.url(repo))
  deps <- tools::package_dependencies(pkg, db = avail, recursive = TRUE)
  if (is.null(deps))
    stop("package not found")

  pkgs <- deps[[1]]
  repo = getOption("repo")
  if (is.null(repo))
    repo <- "https://cloud.r-project.org"

  matches <- avail[ , "Package"] %in% pkgs
  pkg_list <- avail[matches, "Depends"]
  vers <- grep("^R$|^R \\(.*\\)$", pkg_list, value = TRUE)
  vers <- gsub("[^0-9.]", "", vers)
  if (length(vers) == 0)
    return("Not specified")

  max_ver = vers[1]
  if (length(vers) == 1)
    return(max_ver)

  for (v in 2:length(vers))
    if (utils::compareVersion(vers[v], max_ver) > 0)
      max_ver <- vers[v]

  max_ver
}


来源:https://stackoverflow.com/questions/38686427/determine-minimum-r-version-for-all-package-dependencies

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!