Skip to content

Commit

Permalink
Merge pull request #107 from chainsawriot/r131 ref #14
Browse files Browse the repository at this point in the history
R131
  • Loading branch information
chainsawriot authored Mar 6, 2023
2 parents 23b3fc6 + c2a06f4 commit 8d863aa
Show file tree
Hide file tree
Showing 14 changed files with 263 additions and 159 deletions.
50 changes: 33 additions & 17 deletions R/installation.R
Original file line number Diff line number Diff line change
Expand Up @@ -229,6 +229,10 @@
invisible(output_dir)
}

.is_r_version_older_than <- function(rang, r_version = "1.3.1") {
utils::compareVersion(rang$r_version, r_version) == -1
}

.insert_cache_dir <- function(dockerfile_content) {
rang_line <- which(dockerfile_content == "RUN Rscript rang.R")
c(dockerfile_content[1:(rang_line - 1)],
Expand Down Expand Up @@ -322,7 +326,7 @@
export_rang <- function(rang, path, rang_as_comment = TRUE, verbose = TRUE, lib = NA,
cran_mirror = "https://cran.r-project.org/", check_cran_mirror = TRUE,
bioc_mirror = "https://bioconductor.org/packages/") {
if (utils::compareVersion(rang$r_version, "2.1") == -1) {
if (.is_r_version_older_than(rang, "1.3.1")) {
stop("`export_rang` doesn't support this R version (yet).")
}
if (length(rang$ranglets) == 0) {
Expand All @@ -335,14 +339,19 @@ export_rang <- function(rang, path, rang_as_comment = TRUE, verbose = TRUE, lib
stop(cran_mirror, "does not appear to be a valid CRAN mirror.", call. = FALSE)
}
}
if (utils::compareVersion(rang$r_version, "3.3") == -1) { #20
if (.is_r_version_older_than(rang, "3.3")) { #20
cran_mirror <- .normalize_url(cran_mirror, https = FALSE)
}
installation_order <- .generate_installation_order(rang)
file.create(path)
con <- file(path, open="w")
writeLines(readLines(system.file("header.R", package = "rang")), con = con)
cat("installation_order <- ", file = con)
if (.is_r_version_older_than(rang, "2.1")) {
header_file <- "header_cmd.R"
} else {
header_file <- "header.R"
}
writeLines(readLines(system.file(header_file, package = "rang")), con = con)
cat("installation.order <- ", file = con)
dput(installation_order, file = con)
cat("\n", file = con)
cat(paste0("verbose <- ", as.character(verbose), "\n"), file = con)
Expand All @@ -351,9 +360,9 @@ export_rang <- function(rang, path, rang_as_comment = TRUE, verbose = TRUE, lib
} else {
cat(paste0("lib <- \"", as.character(lib), "\"\n"), file = con)
}
cat(paste0("cran_mirror <- \"", cran_mirror, "\"\n"), file = con)
cat(paste0("cran.mirror <- \"", cran_mirror, "\"\n"), file = con)
if(!is.null(rang$bioc_version)) {
cat(paste0("bioc_mirror <- \"", "https://bioconductor.org/packages/",rang$bioc_version,"/", "\"\n"), file = con)
cat(paste0("bioc.mirror <- \"", "https://bioconductor.org/packages/",rang$bioc_version,"/", "\"\n"), file = con)
}
writeLines(readLines(system.file("footer.R", package = "rang")), con = con)
if (isTRUE(rang_as_comment)) {
Expand Down Expand Up @@ -391,7 +400,7 @@ export_renv <- function(rang, path = ".") {
names(pkg_list) <- pkg_df$x
for(i in seq_len(nrow(pkg_df))){
pkg_list[[i]][["Package"]] <- pkg_df$x[i]
pkg_list[[i]][["Version"]] <- pkg_df$version[i]
pkg_list[[i]][["Version"]] <- pkg_df$version[i]
if(pkg_df$source[i]=="cran"){
pkg_list[[i]][["Source"]] <- "Repository"
pkg_list[[i]][["Repository"]] <- "CRAN"
Expand Down Expand Up @@ -438,7 +447,8 @@ export_renv <- function(rang, path = ".") {
#' This applies only to R version >= 3.1
#' @param cache logical, whether to cache the packages now. Please note that the system requirements are not cached. For query with non-CRAN packages, this option is strongly recommended. For query with local packages, this must be TRUE regardless of R version. For R version < 3.1, this must be also TRUE if there is any non-CRAN packages.
#' @param no_rocker logical, whether to skip using Rocker images even when an appropriate version is available. Please keep this as `TRUE` unless you know what you are doing
#' @param debian_version, when Rocker images are not used, which EOL version of Debian to use. Can only be "lenny", "etch", "squeeze", "wheezy", "jessie", "stretch". Please keep this as default "lenny" unless you know what you are doing
#' @param debian_version when Rocker images are not used, which EOL version of Debian to use. Can only be "lenny", "etch", "squeeze", "wheezy", "jessie", "stretch". Please keep this as default "lenny" unless you know what you are doing
#' @param skip_r17 logical, whether to skip R 1.7.x. Currently, it is not possible to compile R 1.7.x (R 1.7.0 and R 1.7.1) with the method provided by `rang`. It affects `snapshot_date` from 2003-04-16 to 2003-10-07. When `skip_r17` is TRUE and `snapshot_date` is within the aforementioned range, R 1.8.0 is used instead.
#' @param ... arguments to be passed to `dockerize`
#' @return `output_dir`, invisibly
#' @inheritParams export_rang
Expand All @@ -461,7 +471,8 @@ dockerize <- function(rang, output_dir, materials_dir = NULL, image = c("r-ver",
cran_mirror = "https://cran.r-project.org/", check_cran_mirror = TRUE,
bioc_mirror = "https://bioconductor.org/packages/",
no_rocker = FALSE,
debian_version = c("lenny", "etch", "squeeze", "wheezy", "jessie", "stretch")) {
debian_version = c("lenny", "squeeze", "wheezy", "jessie", "stretch"),
skip_r17 = TRUE) {
if (length(rang$ranglets) == 0) {
warning("Nothing to dockerize.")
return(invisible(NULL))
Expand All @@ -472,17 +483,18 @@ dockerize <- function(rang, output_dir, materials_dir = NULL, image = c("r-ver",
if (!grepl("^ubuntu", rang$os)) {
stop("System dependencies of ", rang$os, " can't be dockerized.", call. = FALSE)
}
if (utils::compareVersion(rang$r_version, "2.1") == -1) {
if (.is_r_version_older_than(rang, "1.3.1")) {
stop("`dockerize` doesn't support this R version (yet):", rang$r_version, call. = FALSE)
}
if (!is.null(materials_dir) && !(dir.exists(materials_dir))) {
stop(paste0("The folder ", materials_dir, " does not exist"), call. = FALSE)
}
need_cache <- (isTRUE(any(grepl("^github::", .extract_pkgrefs(rang)))) &&
utils::compareVersion(rang$r_version, "3.1") == -1) ||
.is_r_version_older_than(rang, "3.1")) ||
(isTRUE(any(grepl("^bioc::", .extract_pkgrefs(rang)))) &&
utils::compareVersion(rang$r_version, "3.3") == -1) ||
(isTRUE(any(grepl("^local::", .extract_pkgrefs(rang)))))
.is_r_version_older_than(rang, "3.3")) ||
(isTRUE(any(grepl("^local::", .extract_pkgrefs(rang))))) ||
.is_r_version_older_than(rang, "2.1")
if (isTRUE(need_cache) && isFALSE(cache)) {
stop("Packages must be cached. Please set `cache` = TRUE.", call. = FALSE)
}
Expand All @@ -499,16 +511,20 @@ dockerize <- function(rang, output_dir, materials_dir = NULL, image = c("r-ver",
if (isTRUE(cache)) {
.cache_pkgs(rang, output_dir, cran_mirror, bioc_mirror, verbose)
}
if (utils::compareVersion(rang$r_version, "3.1") == -1 || isTRUE(no_rocker)) {
if (isTRUE(skip_r17) && rang$r_version %in% c("1.7.0", "1.7.1")) {
r_version <- "1.8.0"
} else {
r_version <- rang$r_version
}
if (.is_r_version_older_than(rang, "3.1") || isTRUE(no_rocker)) {
file.copy(system.file("compile_r.sh", package = "rang"), file.path(output_dir, "compile_r.sh"),
overwrite = TRUE)

dockerfile_content <- .generate_debian_eol_dockerfile_content(r_version = rang$r_version,
dockerfile_content <- .generate_debian_eol_dockerfile_content(r_version = r_version,
sysreqs_cmd = sysreqs_cmd, lib = lib,
cache = cache,
debian_version = debian_version)
} else {
dockerfile_content <- .generate_rocker_dockerfile_content(r_version = rang$r_version,
dockerfile_content <- .generate_rocker_dockerfile_content(r_version = r_version,
sysreqs_cmd = sysreqs_cmd, lib = lib,
cache = cache, image = image)
}
Expand Down
6 changes: 5 additions & 1 deletion R/resolve.R
Original file line number Diff line number Diff line change
Expand Up @@ -214,7 +214,11 @@
if (isTRUE(no_enhances)) {
disabled_types <- c(disabled_types, "Enhances")
}
res <- dep_df[!dep_df$type %in% disabled_types & dep_df$y != "R" & !(dep_df$y %in% c("datasets", "utils", "grDevices", "graphics", "stats", "methods", "tools", "grid", "splines", "parallel", "stats4", "tcltk", "MASS", "nnet", "class", "spatial")),]
res <- dep_df[!dep_df$type %in% disabled_types &
dep_df$y != "R" & !(dep_df$y %in%
c("datasets", "utils", "grDevices", "graphics", "stats", "methods", "tools",
"grid", "splines", "parallel", "stats4", "tcltk", "MASS", "nnet", "class", "spatial",
"eda", "lqs", "mle", "modreg", "mva", "stepfun", "ts")),]
if (nrow(res) == 0) {
return(NULL)
}
Expand Down
2 changes: 1 addition & 1 deletion README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -162,7 +162,7 @@ With any browser, go to: `local:8787`. The default username is `rstudio`, passwo

## Recreate the computational environment for R < 3.1.0

`rang` can still be used to recreate computational environments for R < 3.1.0. The Dockerfile generated is based on Debian Lenny (5.0) and the requested version of R is compiled from source. As of writing, this method works for R < 3.1.0 but not R < 2.1.0. The `image` parameter is ignored in this case.
`rang` can still be used to recreate computational environments for R < 3.1.0. The Dockerfile generated is based on Debian Lenny (5.0) and the requested version of R is compiled from source. As of writing, this method works for R < 3.1.0 but not R < 1.3.1. The `image` parameter is ignored in this case.

```r
rang_rio <- resolve("rio", snapshot_date = "2013-08-28") ## R 3.0.1
Expand Down
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -193,7 +193,7 @@ With any browser, go to: `local:8787`. The default username is
`rang` can still be used to recreate computational environments for R \<
3.1.0. The Dockerfile generated is based on Debian Lenny (5.0) and the
requested version of R is compiled from source. As of writing, this
method works for R \< 3.1.0 but not R \< 2.1.0. The `image` parameter is
method works for R \< 3.1.0 but not R \< 1.3.1. The `image` parameter is
ignored in this case.

``` r
Expand Down
29 changes: 10 additions & 19 deletions inst/footer.R
Original file line number Diff line number Diff line change
@@ -1,23 +1,14 @@
current_r_version <- paste(R.Version()[c("major","minor")], collapse = ".", sep = "")

## In Unix, all things are file.
## Before you complain, R <= 3.2.0 doesn't have dir.exists.
if (file.exists("cache")) {
path <- "cache"
} else {
path <- tempdir()
}

if (nrow(installation_order) >= 1) {
for (i in seq(from = 1, to = nrow(installation_order), by = 1)) {
x <- installation_order$x[i]
source <- installation_order$source[i]
version <- installation_order$version[i]
handle <- installation_order$handle[i]
uid <- installation_order$uid[i]
.install_from_source(x = x, version = version, handle = handle, source = source, uid = uid,
if (nrow(installation.order) >= 1) {
for (i in seq(from = 1, to = nrow(installation.order), by = 1)) {
x <- installation.order$x[i]
source <- installation.order$source[i]
version <- installation.order$version[i]
handle <- installation.order$handle[i]
uid <- installation.order$uid[i]
.install.from.source(x = x, version = version, handle = handle, source = source, uid = uid,
lib = lib, path = path, verbose = verbose,
cran_mirror = cran_mirror, bioc_mirror = bioc_mirror,
current_r_version = current_r_version)
cran.mirror = cran.mirror, bioc.mirror = bioc.mirror,
current.r.version = current.r.version)
}
}
Loading

0 comments on commit 8d863aa

Please sign in to comment.