Skip to content

Commit

Permalink
Merge pull request #32 from chainsawriot/mattest
Browse files Browse the repository at this point in the history
 Add tests for #23 close #23
  • Loading branch information
chainsawriot authored Feb 11, 2023
2 parents 83865f2 + 0c3455f commit b242b60
Show file tree
Hide file tree
Showing 4 changed files with 105 additions and 30 deletions.
31 changes: 15 additions & 16 deletions R/installation.R
Original file line number Diff line number Diff line change
Expand Up @@ -192,10 +192,10 @@
gran_line <- which(basic_docker == "COPY gran.R ./gran.R")
c(basic_docker[1:gran_line],
"COPY materials/ ./materials/",
basic_docker[(gran_line+1):length(basic_docker)])
basic_docker[(gran_line + 1):length(basic_docker)])
}

.generate_pre310_docker <- function(materials_dir,r_version, debian_version = "lenny", lib, sysreqs_cmd, cache) {
.generate_pre310_docker <- function(r_version, debian_version = "lenny", lib, sysreqs_cmd, cache) {
basic_docker <- c(
paste0("FROM debian/eol:", debian_version),
"ENV TZ UTC",
Expand Down Expand Up @@ -283,9 +283,9 @@ export_granlist <- function(granlist, path, granlist_as_comment = TRUE, verbose
#'
#' This function exports the result from [resolve()] to a Docker file. For R version >= 3.1.0, the Dockerfile is based on the versioned Rocker image.
#' For R version < 3.1.0, the Dockerfile is based on Debian and it compiles R from source.
#' @param output_dir where to put the Docker file
#' @param materials_dir additional resources (e.g. analysis scripts) to be copied into `output_dir`
#' @param image character, which versioned Rocker image to use. Can only be "r-ver", "rstudio", "tidyverse", "verse", "geospatial".
#' @param output_dir character, where to put the Docker file and associated content
#' @param materials_dir character, path to the directiry containing dditional resources (e.g. analysis scripts) to be copied into `output_dir` and in turn into the Docker container
#' @param image character, which versioned Rocker image to use. Can only be "r-ver", "rstudio", "tidyverse", "verse", "geospatial"
#' This applies only to R version <= 3.1
#' @param cache logical, whether to cache the content from CRAN now. Please note that the system requirements are not cached
#' @param ... arguments to be passed to `dockerize`
Expand All @@ -309,13 +309,16 @@ dockerize <- function(granlist, output_dir, materials_dir = NULL, image = c("r-v
granlist_as_comment = TRUE, cache = FALSE, verbose = TRUE, lib = NA,
cran_mirror = "https://cran.r-project.org/", check_cran_mirror = TRUE) {
if (missing(output_dir)) {
stop("You must provide `output_dir`.")
stop("You must provide `output_dir`.", call. = FALSE)
}
if (!grepl("^ubuntu", granlist$os)) {
stop("System dependencies of ", granlist$os, " can't be dockerized.")
stop("System dependencies of ", granlist$os, " can't be dockerized.", call. = FALSE)
}
if (utils::compareVersion(granlist$r_version, "2.1") == -1) {
stop("`dockerize` doesn't support this R version (yet).")
stop("`dockerize` doesn't support this R version (yet):", granlist$r_version, call. = FALSE)
}
if (!is.null(materials_dir) && !(dir.exists(materials_dir))) {
stop(paste0("The folder ", materials_dir, " does not exist"), call. = FALSE)
}
image <- match.arg(image)
sysreqs_cmd <- .consolidate_sysreqs(granlist)
Expand Down Expand Up @@ -350,19 +353,15 @@ dockerize <- function(granlist, output_dir, materials_dir = NULL, image = c("r-v
basic_docker <- .insert_cache_dir(basic_docker)
}
}
if(!is.null(materials_dir)){
if(!dir.exists(materials_dir)){
stop(paste0("The folder ",materials_dir," does not exist"),call. = FALSE)
} else{
out_mat_dir <- paste0(output_dir,"/materials")
if (!dir.exists(out_mat_dir)) {
dir.create(out_mat_dir)
if (!(is.null(materials_dir))) {
out_mat_dir <- file.path(output_dir, "materials")
if (isFALSE(dir.exists(out_mat_dir))) {
dir.create(out_mat_dir)
}
file.copy(list.files(materials_dir, full.names = TRUE),
out_mat_dir,
recursive = TRUE)
basic_docker <- .insert_materials_dir(basic_docker)
}
}
writeLines(basic_docker, file.path(output_dir, "Dockerfile"))
invisible(output_dir)
Expand Down
6 changes: 3 additions & 3 deletions man/dockerize.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

90 changes: 81 additions & 9 deletions tests/testthat/test_dockerize.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,15 @@
.gen_temp_dir <- function() {
file.path(tempdir(), paste(sample(c(LETTERS, letters), 20, replace = TRUE), collapse = ""))
}

test_that("defensive programming", {
graph <- readRDS("../testdata/sle_graph.RDS")
expect_error(dockerize(graph, output_dir = tempdir()))
})

test_that("integration of #13 in dockerize()", {
gran_ok <- readRDS("../testdata/gran_ok.RDS")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
dockerize(granlist = gran_ok, output_dir = temp_dir) ## granlist_as_comment = TRUE
x <- readLines(file.path(temp_dir, "gran.R"))
expect_true(any(grepl("^## ## To reconstruct this file", x)))
Expand All @@ -17,7 +21,7 @@ test_that("integration of #13 in dockerize()", {
test_that("integration of #16 in dockerize()", {
## verbose
gran_ok <- readRDS("../testdata/gran_ok.RDS")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
dockerize(granlist = gran_ok, output_dir = temp_dir) ## verbose = TRUE
x <- readLines(file.path(temp_dir, "gran.R"))
expect_true(any(grepl("^verbose <- TRUE", x)))
Expand All @@ -39,7 +43,7 @@ test_that("integration of #16 in dockerize()", {

test_that("integration of #18 in dockerize()", {
gran_ok <- readRDS("../testdata/gran_ok.RDS")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
dockerize(granlist = gran_ok, output_dir = temp_dir) ## cran_mirror = "https://cran.r-project.org/"
x <- readLines(file.path(temp_dir, "gran.R"))
expect_true(any(grepl("^cran_mirror <- \"https://cran\\.r\\-project\\.org/\"", x)))
Expand All @@ -58,7 +62,7 @@ test_that("integration of #18 in dockerize()", {
test_that("integration of #20 to dockerize()", {
gran_ok <- readRDS("../testdata/gran_ok.RDS")
expect_equal(gran_ok$r_version, "4.2.2")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
dockerize(gran_ok, output_dir = temp_dir) ## cran_mirror = "https://cran.r-project.org/"
x <- readLines(file.path(temp_dir, "gran.R"))
expect_true(any(grepl("^cran_mirror <- \"https://cran\\.r\\-project\\.org/\"", x)))
Expand All @@ -70,15 +74,15 @@ test_that("integration of #20 to dockerize()", {
gran_ok <- readRDS("../testdata/gran_ok.RDS")
gran_ok$r_version <- "3.2.0"
dockerize(gran_ok, output_dir = temp_dir) ## cran_mirror = "https://cran.r-project.org/"
x <- readLines(file.path(temp_dir, "gran.R"))
x <- readLines(file.path(temp_dir, "gran.R"))
expect_false(any(grepl("^cran_mirror <- \"https://cran\\.r\\-project\\.org/\"", x)))
expect_true(any(grepl("^cran_mirror <- \"http://cran\\.r\\-project\\.org/\"", x)))
})

test_that("Dockerize R < 3.1 and >= 2.1", {
gran_rio <- readRDS("../testdata/gran_rio_old.RDS")
expect_equal(gran_rio$r_version, "3.0.1")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
dockerize(gran_rio, output_dir = temp_dir)
expect_true(file.exists(file.path(temp_dir, "compile_r.sh")))
Dockerfile <- readLines(file.path(temp_dir, "Dockerfile"))
Expand All @@ -92,11 +96,11 @@ test_that("Dockerize R < 3.1 and >= 2.1", {
test_that("Docker R < 2.1", {
gran_rio <- readRDS("../testdata/gran_rio_old.RDS")
gran_rio$r_version <- "2.1.0" ## exactly 2.1.0, no error
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
expect_error(dockerize(gran_rio, output_dir = temp_dir), NA)
gran_rio <- readRDS("../testdata/gran_rio_old.RDS")
gran_rio$r_version <- "2.0.0"
expect_error(dockerize(gran_rio, output_dir = temp_dir))
expect_error(dockerize(gran_rio, output_dir = temp_dir))
})

test_that(".consolidate_sysreqs and issue #21", {
Expand All @@ -115,6 +119,74 @@ test_that(".consolidate_sysreqs and issue #21", {

test_that("Dockerize warning, issue #21", {
graph <- readRDS("../testdata/issue21.RDS")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
expect_warning(dockerize(graph, output_dir = temp_dir))
})

test_that("material_dir, non-existing, #23", {
## normal case
gran_rio <- readRDS("../testdata/gran_rio_old.RDS")
temp_dir <- .gen_temp_dir()
expect_error(dockerize(gran_rio, output_dir = temp_dir, materials_dir = NULL), NA)
## non-existing
fake_material_dir <- .gen_temp_dir()
expect_false(dir.exists(fake_material_dir))
expect_error(dockerize(gran_rio, output_dir = temp_dir, materials_dir = fake_material_dir))
})

test_that("material_dir, existing, no subdir, #23", {
## exist, but empty dir
## Pre R 3.1.0
gran_rio <- readRDS("../testdata/gran_rio_old.RDS")
temp_dir <- .gen_temp_dir()
fake_material_dir <- .gen_temp_dir()
dir.create(fake_material_dir)
dockerize(gran_rio, output_dir = temp_dir, materials_dir = fake_material_dir)
expect_true(dir.exists(file.path(temp_dir, "materials")))
expect_equal(list.files(file.path(temp_dir, "materials")), character(0))
expect_true(any(readLines(file.path(temp_dir, "Dockerfile")) == "COPY materials/ ./materials/"))
## Post R 3.1.0
graph <- readRDS("../testdata/graph.RDS")
temp_dir <- .gen_temp_dir()
fake_material_dir <- .gen_temp_dir()
dir.create(fake_material_dir)
dockerize(graph, output_dir = temp_dir, materials_dir = fake_material_dir)
expect_true(dir.exists(file.path(temp_dir, "materials")))
expect_equal(list.files(file.path(temp_dir, "materials")), character(0))
expect_true(any(readLines(file.path(temp_dir, "Dockerfile")) == "COPY materials/ ./materials/"))
## Will only test post 3.1.0 from now on
## some files in fake_material_dir
temp_dir <- .gen_temp_dir()
fake_material_dir <- .gen_temp_dir()
dir.create(fake_material_dir)
file.copy("../testdata/graph.RDS", file.path(fake_material_dir, "graph.RDS"))
writeLines(c("831721", "GESIS"), file.path(fake_material_dir, "test.R"))
dockerize(graph, output_dir = temp_dir, materials_dir = fake_material_dir)
expect_true(dir.exists(file.path(temp_dir, "materials")))
expect_equal(list.files(file.path(temp_dir, "materials")), c("graph.RDS", "test.R"))
expect_true(any(readLines(file.path(temp_dir, "Dockerfile")) == "COPY materials/ ./materials/"))
expect_true(file.exists(file.path(temp_dir, "materials", "graph.RDS")))
expect_true(file.exists(file.path(temp_dir, "materials", "test.R")))
content <- readLines(file.path(temp_dir, "materials", "test.R"))
expect_equal(content[1], "831721")
expect_equal(content[2], "GESIS")
})

test_that("material_dir, existing, with 1 subdir, #23", {
temp_dir <- .gen_temp_dir()
fake_material_dir <- .gen_temp_dir()
dir.create(fake_material_dir)
dir.create(file.path(fake_material_dir, "data"))
file.copy("../testdata/graph.RDS", file.path(fake_material_dir, "data", "graph.RDS"))
writeLines(c("831721", "GESIS"), file.path(fake_material_dir, "test.R"))
graph <- readRDS("../testdata/graph.RDS")
dockerize(graph, output_dir = temp_dir, materials_dir = fake_material_dir)
expect_true(dir.exists(file.path(temp_dir, "materials")))
expect_true(any(readLines(file.path(temp_dir, "Dockerfile")) == "COPY materials/ ./materials/"))
expect_true(dir.exists(file.path(temp_dir, "materials", "data")))
expect_true(file.exists(file.path(temp_dir, "materials", "data", "graph.RDS")))
expect_true(file.exists(file.path(temp_dir, "materials", "test.R")))
content <- readLines(file.path(temp_dir, "materials", "test.R"))
expect_equal(content[1], "831721")
expect_equal(content[2], "GESIS")
})
8 changes: 6 additions & 2 deletions tests/testthat/test_resolve.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
.gen_temp_dir <- function() {
file.path(tempdir(), paste(sample(c(LETTERS, letters), 20, replace = TRUE), collapse = ""))
}

test_that("defensive programming", {
expect_error(resolve("LDAvis", os = "windows"))
})
Expand Down Expand Up @@ -48,7 +52,7 @@ test_that("cache #17", {
skip_if_offline()
skip_on_cran()
gran_ok <- readRDS("../testdata/gran_ok.RDS")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
dockerize(gran_ok, output_dir = temp_dir) ## cache = FALSE
x <- readLines(file.path(temp_dir, "Dockerfile"))
expect_false(any(grepl("^COPY cache", x)))
Expand All @@ -71,7 +75,7 @@ test_that("cache for R < 3.1 and R >= 2.1", {
skip_on_cran()
gran_rio <- readRDS("../testdata/gran_rio_old.RDS")
expect_equal(gran_rio$r_version, "3.0.1")
temp_dir <- file.path(tempdir(), sample(1:10000, size = 1))
temp_dir <- .gen_temp_dir()
dockerize(gran_rio, output_dir = temp_dir, cache = TRUE, verbose = FALSE)
x <- readLines(file.path(temp_dir, "Dockerfile"))
expect_true(any(grepl("^COPY cache", x)))
Expand Down

0 comments on commit b242b60

Please sign in to comment.