Skip to content

Commit

Permalink
Add predetection of packages based on automagic
Browse files Browse the repository at this point in the history
closes o2r-project#53 and o2r-project#101;
also update base images to 3.4.4
  • Loading branch information
nuest committed Mar 23, 2018
1 parent 1d4190e commit ba5ccc5
Show file tree
Hide file tree
Showing 12 changed files with 319 additions and 127 deletions.
5 changes: 3 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,8 @@ Imports:
sysreqs,
futile.logger,
devtools,
semver
semver,
automagic
VignetteBuilder: knitr
Description: Package R sessions, scripts, workspaces and vignettes together with
all dependencies to execute them in Docker containers. This package is supported
Expand Down Expand Up @@ -48,7 +49,7 @@ Suggests:
remotes,
ggplot2
RoxygenNote: 6.0.1
Collate:
Collate:
'Class-Instruction.R'
'Class-Add.R'
'Class-All.R'
Expand Down
142 changes: 67 additions & 75 deletions R/dockerfile.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@
#' @param add_self Whether to add the package containerit itself if loaded/attached to the session
#' @param vanilla Whether to use an empty vanilla session when packaging scripts and markdown files (equivalent to \code{R --vanilla})
#' @param silent Whether or not to print information during execution
#' @param predetect Extract the required libraries based on \code{library} calls using the package \code{automagic} before running a script/document
#' @param versioned_libs [EXPERIMENTAL] Whether it shall be attempted to match versions of linked external libraries
#' @param versioned_packages [EXPERIMENTAL] Whether it shall be attempted to match versions of R packages
#'
Expand Down Expand Up @@ -73,6 +74,7 @@ dockerfile <- function(from = utils::sessionInfo(),
add_self = FALSE,
vanilla = TRUE,
silent = FALSE,
predetect = TRUE,
versioned_libs = FALSE,
versioned_packages = FALSE) {
if (silent) {
Expand Down Expand Up @@ -162,10 +164,9 @@ dockerfile <- function(from = utils::sessionInfo(),
futile.logger::flog.debug("Creating from character string '%s'", from)

if (dir.exists(from)) {
futile.logger::flog.debug("'%s' is a directory")
futile.logger::flog.debug("'%s' is a directory", from)
.originalFrom <- from
.dockerfile <-
dockerfileFromWorkspace(
.dockerfile <- dockerfileFromWorkspace(
path = from,
.dockerfile = .dockerfile,
soft = soft,
Expand All @@ -174,15 +175,14 @@ dockerfile <- function(from = utils::sessionInfo(),
copy = copy,
vanilla = vanilla,
silent = silent,
predetect = predetect,
versioned_libs = versioned_libs,
versioned_packages = versioned_packages,
workdir = workdir
)
workdir = workdir)
} else if (file.exists(from)) {
futile.logger::flog.debug("'%s' is a file", from)
.originalFrom <- from
.dockerfile <-
dockerfileFromFile(
.dockerfile <- dockerfileFromFile(
file = from,
.dockerfile = .dockerfile,
soft = soft,
Expand All @@ -191,10 +191,10 @@ dockerfile <- function(from = utils::sessionInfo(),
copy = copy,
vanilla = vanilla,
silent = silent,
predetect = predetect,
versioned_libs = versioned_libs,
versioned_packages = versioned_packages,
workdir = workdir
)
workdir = workdir)
} else {
stop("Unsupported string for 'from' argument (not a file, not a directory): ", from)
}
Expand Down Expand Up @@ -278,23 +278,24 @@ dockerfileFromSession <- function(session,
return(.dockerfile)
}

dockerfileFromFile <-
function(file,
.dockerfile,
soft,
copy,
offline,
add_self,
vanilla,
silent,
versioned_libs,
versioned_packages,
workdir) {
dockerfileFromFile <- function(file,
.dockerfile,
soft,
copy,
offline,
add_self,
vanilla,
silent,
predetect,
versioned_libs,
versioned_packages,
workdir) {
futile.logger::flog.debug("Creating from file")

# prepare context ( = working directory) and normalize paths:
context = normalizePath(getwd())
file = normalizePath(file)
futile.logger::flog.debug("Working with file %s in working directory %s", file, context)

#Is the file within the context?
len = stringr::str_length(context)
Expand All @@ -307,41 +308,34 @@ dockerfileFromFile <-

# execute script / markdowns or read Rdata file to obtain sessioninfo
if (stringr::str_detect(file, ".R$")) {
futile.logger::flog.info("Executing R script file in %s locally.", rel_path)
sessionInfo <-
obtain_localSessionInfo(
file = file,
vanilla = vanilla,
slave = silent,
echo = !silent
)
futile.logger::flog.info("Processing R script file '%s' locally.", rel_path)
sessionInfo <- obtain_localSessionInfo(file = file,
vanilla = vanilla,
slave = silent,
echo = !silent,
predetect = predetect)
} else if (stringr::str_detect(file, ".Rmd$")) {
futile.logger::flog.info("Processing the given file %s locally using rmarkdown::render(...)", rel_path)
sessionInfo <-
obtain_localSessionInfo(
rmd_file = file,
vanilla = vanilla,
slave = silent,
echo = !silent
)
futile.logger::flog.info("Processing Rmd file '%s' locally using rmarkdown::render(...)", rel_path)
sessionInfo <- obtain_localSessionInfo(rmd_file = file,
vanilla = vanilla,
slave = silent,
echo = !silent,
predetect = predetect)
} else if (stringr::str_detect(file, ".Rdata$")) {
sessionInfo <- getSessionInfoFromRdata(file)
} else{
futile.logger::flog.info("The supplied file %s has no known extension. containerit will handle it as an R script for packaging.", rel_path)
}

# append system dependencies and package installation instructions
.dockerfile <-
dockerfileFromSession(
session = sessionInfo,
.dockerfile = .dockerfile,
soft = soft,
offline = offline,
add_self = add_self,
versioned_libs = versioned_libs,
versioned_packages = versioned_packages,
workdir = workdir
)
.dockerfile <- dockerfileFromSession(session = sessionInfo,
.dockerfile = .dockerfile,
soft = soft,
offline = offline,
add_self = add_self,
versioned_libs = versioned_libs,
versioned_packages = versioned_packages,
workdir = workdir)

## working directory must be set before. Now add copy instructions
if (!is.null(copy) && !is.na(copy)) {
Expand Down Expand Up @@ -370,8 +364,7 @@ dockerfileFromFile <-
sapply(copy, function(file) {
if (file.exists(file)) {
rel_path <- .makeRelative(normalizePath(file), context)
rel_path_dest <-
stringr::str_replace_all(rel_path, pattern = "\\\\", replacement = "/")
rel_path_dest <- stringr::str_replace_all(rel_path, pattern = "\\\\", replacement = "/")
if (dir.exists(file) &&
!stringr::str_detect(rel_path_dest, "/$"))
rel_path_dest <- paste0(rel_dir_dest, "/")
Expand All @@ -389,18 +382,18 @@ dockerfileFromFile <-
return(.dockerfile)
}

dockerfileFromWorkspace <-
function(path,
.dockerfile,
soft,
offline,
add_self,
copy,
vanilla,
silent,
versioned_libs,
versioned_packages,
workdir) {
dockerfileFromWorkspace <- function(path,
.dockerfile,
soft,
offline,
add_self,
copy,
vanilla,
silent,
predetect,
versioned_libs,
versioned_packages,
workdir) {
futile.logger::flog.debug("Creating from workspace directory")
target_file <- NULL #file to be packaged

Expand Down Expand Up @@ -443,19 +436,18 @@ dockerfileFromWorkspace <-
else
futile.logger::flog.info("Found file for packaging in workspace: %s", target_file)

.df <- dockerfileFromFile(
target_file,
.dockerfile = .dockerfile,
soft = soft,
offline = offline,
copy = copy,
add_self = add_self,
vanilla = vanilla,
silent = silent,
versioned_libs = versioned_libs,
versioned_packages = versioned_packages,
workdir = workdir
)
.df <- dockerfileFromFile(target_file,
.dockerfile = .dockerfile,
soft = soft,
offline = offline,
copy = copy,
add_self = add_self,
vanilla = vanilla,
silent = silent,
predetect = predetect,
versioned_libs = versioned_libs,
versioned_packages = versioned_packages,
workdir = workdir)
return(.df)
}

Expand Down
85 changes: 54 additions & 31 deletions R/sessionInfo-localbuild-methods.R
Original file line number Diff line number Diff line change
Expand Up @@ -99,51 +99,74 @@ create_localDockerImage <- function(x,
#
# This method is used for packaging R scripts (see dockerFileFromFile)
# and for comparing session information (see test/testthat/test_sessioninfo_repoduce.R)
obtain_localSessionInfo <-
function(expr = c(),
obtain_localSessionInfo <- function(expr = c(),
file = NULL, # an R script to be executed
rmd_file = NULL, # an R Markdown file
vanilla = TRUE,
silent = TRUE,
slave = FALSE,
echo = FALSE, #whether R scripts should be 'echoed'
echo = FALSE, # whether R scripts should be 'echoed'
predetect = TRUE, # whether to use automagic to make sure all required packages are installed
local_tempfile = tempfile(pattern = "rdata-sessioninfo"),
local_temp_script = tempfile(pattern = "r-script")) {
#append commands to create a local sessionInfo
if (!is.null(file) && file.exists(file)) {
expr <- append(expr, call("source", file = file, echo = echo))
#append commands to create a local sessionInfo
required_pkgs <- c()
if (!is.null(file) && file.exists(file)) {
expr <- append(expr, call("source", file = file, echo = echo))

if (predetect) {
required_pkgs <- automagic::parse_packages(file)
futile.logger::flog.debug("Analysed input file %s and found required packages: %s",
file, toString(required_pkgs))
}
}

if (!is.null(rmd_file) && file.exists(rmd_file)) {
render_call <- quote(rmarkdown::render("file"))
render_call[[2]] <- rmd_file #replace the argument "file
expr <- append(expr, render_call)

if (!is.null(rmd_file) && file.exists(rmd_file)) {
render_call <- quote(rmarkdown::render("file"))
render_call[[2]] <- rmd_file #replace the argument "file
expr <- append(expr, render_call)
if (predetect) {
required_pkgs <- automagic::parse_packages(rmd_file)
futile.logger::flog.debug("Analysed input file %s and found required packages: %s",
rmd_file, toString(required_pkgs))
}
}

expr <- append(expr, .writeSessionInfoExp(local_tempfile))
args <- .exprToParam(expr, to_string = TRUE)
if (vanilla)
args <- append("--vanilla", args)
if (predetect && length(required_pkgs) > 0) {
installing_pkgs <- stringr::str_remove_all(required_pkgs, "\"")
installing_pkgs <- setdiff(installing_pkgs, rownames(installed.packages()))
if (length(installing_pkgs) > 0) {
futile.logger::flog.info("Missing packages installed before running file: %s",
toString(installing_pkgs))
install.packages(pkgs = installing_pkgs)
} else {
futile.logger::flog.debug("No missing packages to install before running file")
}
}

if (slave)
args <- append("--slave", args)
expr <- append(expr, .writeSessionInfoExp(local_tempfile))
args <- .exprToParam(expr, to_string = TRUE)
if (vanilla)
args <- append("--vanilla", args)

if (silent)
args <- append("--silent", args)
if (slave)
args <- append("--slave", args)

futile.logger::flog.info(paste(
"Creating an R session with the following arguments:\n\t R ",
paste(args, collapse = " ")
))
if (silent)
args <- append("--silent", args)

system2("R", args)
futile.logger::flog.info(paste("Creating an R session with the following arguments:\n\t R ",
paste(args, collapse = " ")))

if (!file.exists(local_tempfile))
stop("Failed to execute the script locally! A sessionInfo could not be determined.")
system2("R", args)

load(local_tempfile)
#clean up:
unlink(local_tempfile)
unlink(local_temp_script)
return(get("info"))
}
if (!file.exists(local_tempfile))
stop("Failed to execute the script locally! A sessionInfo could not be determined.")

load(local_tempfile)
#clean up:
unlink(local_tempfile)
unlink(local_temp_script)
return(get("info"))
}
26 changes: 11 additions & 15 deletions R/utility-functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -190,18 +190,14 @@ getSessionInfoFromRdata <- function(file) {
#'
#' @return An object of class session info (Can be used as an input to the dockerfile-method)
#' @export
#'
clean_session <-
function(expr = list(),
file = NULL,
vanilla = TRUE,
slave = FALSE,
echo = FALSE) {
obtain_localSessionInfo(
expr = expr,
file = file,
slave = slave,
echo = echo,
vanilla = vanilla
)
}
clean_session <- function(expr = list(),
file = NULL,
vanilla = TRUE,
slave = FALSE,
echo = FALSE) {
obtain_localSessionInfo(expr = expr,
file = file,
slave = slave,
echo = echo,
vanilla = vanilla)
}
2 changes: 1 addition & 1 deletion inst/docker/Dockerfile
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
FROM rocker/verse:3.4.3
FROM rocker/verse:3.4.4

RUN apt-get update \
&& apt-get install -y --no-install-recommends \
Expand Down
Loading

0 comments on commit ba5ccc5

Please sign in to comment.