Skip to content

Commit

Permalink
Merge pull request #53 from MD-Anderson-Bioinformatics/v1.0.2_mary
Browse files Browse the repository at this point in the history
Installation improvements
  • Loading branch information
marohrdanz authored Mar 28, 2024
2 parents e874633 + 5293eda commit 7aac307
Show file tree
Hide file tree
Showing 10 changed files with 239 additions and 27 deletions.
5 changes: 3 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Type: Package
Package: NGCHM
Title: Next Generation Clustered Heat Maps
Version: 1.0.1
Version: 1.0.2
Authors@R: c(
person(c("Bradley", "M"), "Broom", , "[email protected]", role = "aut",
comment = c(ORCID = "0000-0002-0915-3164")),
Expand Down Expand Up @@ -47,6 +47,7 @@ Encoding: UTF-8
Roxygen: list(markdown = TRUE)
RoxygenNote: 7.2.3
Collate:
'internalFunctions.R'
'allClasses.R'
'allGenerics.R'
'allMethods.R'
Expand All @@ -58,5 +59,5 @@ Collate:
'zzz.R'
'package.R'
SystemRequirements:
Java (>= 8.0)
Java (>= 11)
Git
79 changes: 56 additions & 23 deletions R/functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -159,6 +159,7 @@ ngchmGetEnv <- function() {
#' This function creates a Next Generation Clustered Heat Map (NGCHM) object in memory.
#' Additional parameters will be added to the new NGCHM (see chmAdd).
#' The bare NGCHM needs at least one data layer added to it before it can be compiled.
#' This function requires **git** to be installed.
#'
#' @param name The name under which the NGCHM will be saved to the NGCHM server.
#' @param ... Zero or more initial objects to include in the NGCHM (see chmAdd).
Expand Down Expand Up @@ -2999,17 +3000,6 @@ getServerVersion <- function(server) {
as.numeric(ngchmResponseJSON(res)$Build_Number)
}

testExternalProgram <- function(program) {
res <- NULL
suppressWarnings(try(
{
res <- system2(program, NULL, stdout = TRUE, stderr = TRUE)
},
silent = TRUE
))
if (is.null(res)) warning(sprintf("Unable to execute external program '%s'. Some functionality not available.", program))
!is.null(res)
}

testJava <- function(jarfile) {
res <- NULL
Expand Down Expand Up @@ -3728,6 +3718,13 @@ readTile <- function(filename, nrow, ncol) {
#' Export a standalone NGCHM to a file.
#'
#' Create a standalone viewer for the NGCHM in the specified file.
#' This function requires **Java 11** and the
#' **[NGCHMSupportFiles](https://github.com/MD-Anderson-Bioinformatics/NGCHMSupportFiles)** package.
#'
#' The NGCHMSupportFiles package can be installed from the R-universe repository: \cr\cr
#' \code{install.packages('NGCHMDemoData', } \cr
#' \code{repos = c('https://md-anderson-bioinformatics.r-universe.dev',} \cr
#' \code{'https://cloud.r-project.org'))}
#'
#' @export
#' @rdname chmExportToFile-method
Expand All @@ -3745,16 +3742,23 @@ chmExportToFile <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shai
if (missing(shaidyMapGen)) shaidyMapGen <- Sys.getenv("SHAIDYMAPGEN")
if (missing(shaidyMapGenJava)) shaidyMapGenJava <- Sys.getenv("SHAIDYMAPGENJAVA")
if (shaidyMapGenJava == "") shaidyMapGenJava <- "java"
if (!checkForJavaVersion(shaidyMapGenJava)) {
stop("Missing required java version.")
}
if (missing(shaidyMapGenArgs)) shaidyMapGenArgs <- strsplit(Sys.getenv("SHAIDYMAPGENARGS"), ",")[[1]]
if (shaidyMapGen == "") stop("shaidyMapGen not specified or set in environment")

if (shaidyMapGen == "") {
checkForNGCHMSupportFiles()
stop("Missing required path to ShaidyMapGen.jar file.")
}
chm@format <- "shaidy"
chm <- chmAddProperty(chm, "chm.info.build.time", format(Sys.time(), "%F %H:%M:%S"))
chm <- chmMake(chm)

shaidyRepo <- ngchm.env$tmpShaidy
shaid <- shaidyGetShaid(chm)
status <- system2(shaidyMapGenJava, c(shaidyMapGenArgs, "-jar", shaidyMapGen, shaidyRepo$basepath, shaid@value, shaid@value, "NO_PDF"))
status <- system2(shaidyMapGenJava,
c(shaidyMapGenArgs, "-jar", shaidyMapGen, shaidyRepo$basepath, shaid@value, shaid@value, "NO_PDF"),
env = c("DISPLAY=''")) # Set DISPLAY to empty string to prevent X11 errors in Rstudio Docker container
if (status != 0) stop("export to ngchm failed")
if (!file.copy(shaidyRepo$blob.path("viewer", shaid@value, chm@name, paste(chm@name, "ngchm", sep = ".")), filename, TRUE)) {
stop("export to ngchm failed")
Expand All @@ -3765,6 +3769,13 @@ chmExportToFile <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shai
#' Export a PDF of the NGCHM to a file.
#'
#' Create a PDF of the NGCHM in the specified file.
#' This function requires **Java 11** and the
#' **[NGCHMSupportFiles](https://github.com/MD-Anderson-Bioinformatics/NGCHMSupportFiles)** package.
#'
#' The NGCHMSupportFiles package can be installed from the R-universe repository: \cr\cr
#' \code{install.packages('NGCHMDemoData', } \cr
#' \code{repos = c('https://md-anderson-bioinformatics.r-universe.dev',} \cr
#' \code{'https://cloud.r-project.org'))}
#'
#' @export
#' @rdname chmExportToPDF-method
Expand All @@ -3780,8 +3791,15 @@ chmExportToFile <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shai
chmExportToPDF <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shaidyMapGenJava, shaidyMapGenArgs) {
if (!overwrite && file.exists(filename)) stop("'filename' already exists")
if (missing(shaidyMapGen)) shaidyMapGen <- Sys.getenv("SHAIDYMAPGEN")
if (shaidyMapGen == "") {
checkForNGCHMSupportFiles()
stop("Missing required path to ShaidyMapGen.jar file.")
}
if (missing(shaidyMapGenJava)) shaidyMapGenJava <- Sys.getenv("SHAIDYMAPGENJAVA")
if (shaidyMapGenJava == "") shaidyMapGenJava <- "java"
if (!checkForJavaVersion(shaidyMapGenJava)) {
stop("Missing required java version.")
}
if (missing(shaidyMapGenArgs)) shaidyMapGenArgs <- strsplit(Sys.getenv("SHAIDYMAPGENARGS"), ",")[[1]]

if (length(chmProperty(chm, "chm.info.build.time")) == 0) {
Expand All @@ -3795,8 +3813,9 @@ chmExportToPDF <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shaid

pdfpath <- shaidyRepo$blob.path("viewer", shaid@value, chm@name, paste(chm@name, ".pdf", sep = ""))
if (!file.exists(pdfpath)) {
if (shaidyMapGen == "") stop("shaidyMapGen required but not specified or set in environment")
status <- system2(shaidyMapGenJava, c(shaidyMapGenArgs, "-jar", shaidyMapGen, shaidyRepo$basepath, shaid@value, shaid@value))
status <- system2(shaidyMapGenJava,
c(shaidyMapGenArgs, "-jar", shaidyMapGen, shaidyRepo$basepath, shaid@value, shaid@value),
env = c("DISPLAY=''")) # Set DISPLAY to empty string to prevent X11 errors in Rstudio Docker container
if (status != 0 || !file.exists(pdfpath)) stop("export to pdf failed")
}

Expand All @@ -3808,6 +3827,13 @@ chmExportToPDF <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shaid
#' Export a standalone HTML containing the NGCHM to a file.
#'
#' Create a standalone HTML containing the NGCHM in the specified file.
#' This function requires **Java 11** and the
#' **[NGCHMSupportFiles](https://github.com/MD-Anderson-Bioinformatics/NGCHMSupportFiles)** package.
#'
#' The NGCHMSupportFiles package can be installed from the R-universe repository: \cr\cr
#' \code{install.packages('NGCHMDemoData', } \cr
#' \code{repos = c('https://md-anderson-bioinformatics.r-universe.dev',} \cr
#' \code{'https://cloud.r-project.org'))}
#'
#' @export
#' @rdname chmExportToHTML-method
Expand All @@ -3824,16 +3850,22 @@ chmExportToPDF <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shaid
chmExportToHTML <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shaidyMapGenJava, shaidyMapGenArgs, ngchmWidgetPath) {
if (!overwrite && file.exists(filename)) stop("'filename' already exists")
if (missing(shaidyMapGen)) shaidyMapGen <- Sys.getenv("SHAIDYMAPGEN")
if (shaidyMapGen == "") {
checkForNGCHMSupportFiles()
stop("Missing required path to ShaidyMapGen.jar file.")
}
if (missing(shaidyMapGenJava)) shaidyMapGenJava <- Sys.getenv("SHAIDYMAPGENJAVA")
if (shaidyMapGenJava == "") shaidyMapGenJava <- "java"
if (!checkForJavaVersion(shaidyMapGenJava)) {
stop("Missing required java version.")
}
if (missing(shaidyMapGenArgs)) shaidyMapGenArgs <- strsplit(Sys.getenv("SHAIDYMAPGENARGS"), ",")[[1]]
if (missing(ngchmWidgetPath)) {
stopifnot(Sys.getenv("NGCHMWIDGETPATH") != "")
} else {
Sys.setenv(NGCHMWIDGETPATH = ngchmWidgetPath)
if (missing(ngchmWidgetPath)) ngchmWidgetPath <- Sys.getenv("NGCHMWIDGETPATH")
if (ngchmWidgetPath == "") {
checkForNGCHMSupportFiles()
stop("Missing required path to ngchmWidget-min.js file.")
}


if (length(chmProperty(chm, "chm.info.build.time")) == 0) {
chm@format <- "shaidy"
chmProperty(chm, "chm.info.build.time") <- format(Sys.time(), "%F %H:%M:%S")
Expand All @@ -3845,8 +3877,9 @@ chmExportToHTML <- function(chm, filename, overwrite = FALSE, shaidyMapGen, shai

htmlpath <- shaidyRepo$blob.path("viewer", shaid@value, chm@name, paste(chm@name, ".html", sep = ""))
if (!file.exists(htmlpath)) {
if (shaidyMapGen == "") stop("shaidyMapGen required but not specified or set in environment")
status <- system2(shaidyMapGenJava, c(shaidyMapGenArgs, "-jar", shaidyMapGen, shaidyRepo$basepath, shaid@value, shaid@value, "NO_PDF", "-HTML"))
status <- system2(shaidyMapGenJava,
c(shaidyMapGenArgs, "-jar", shaidyMapGen, shaidyRepo$basepath, shaid@value, shaid@value, "NO_PDF", "-HTML"),
env = c("DISPLAY=''")) # Set DISPLAY to empty string to prevent X11 errors in Rstudio Docker container
if (status != 0 || !file.exists(htmlpath)) stop("export to html failed")
}

Expand Down
128 changes: 128 additions & 0 deletions R/internalFunctions.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,128 @@
#' Check for External Utilities used by NGCHM
#'
#' This function checks for the presence of certain external programs that are suggested for the package to
#' function properly. It checks for 'git', 'scp', 'ssh', and 'tar'. If any of these programs are not found,
#' it prints a warning.
#'
#' @param None.
#'
#' @return None. This function is called for its side effects (printing warnings if necessary programs are not found).
#'
#' @noRd
#' @keywords internal
checkForExternalUtilities <- function() {
suggestedUtilities <- list(
"git" = paste0("CRITICAL WARNING: Unable to verify 'git' installation. Git is required to create NG-CHMs. ",
"Install git in order to create NG-CHMs."),
"scp" = "Missing suggested external program 'scp'. Some server functionality unavailable.",
"ssh" = "Missing suggested external program 'ssh'. Some server functionality unavailable.",
"tar" = "Missing suggested external program 'tar'. Some server functionality unavailable."
)
for (name in names(suggestedUtilities)) {
checkResponse <- NULL
suppressWarnings(try({
checkResponse <- system2(name, "--version", stdout = TRUE, stderr = TRUE)
}, silent = TRUE))
if (is.null(checkResponse)) {
warning(suggestedUtilities[[name]])
}
}
}

#' Check Java Version
#'
#' This function checks if the Java is installed and if the installed version meets the required version.
#' It extracts the major version number from the Java version string and compares it with the required version.
#'
#' @param requiredJavaVersion The required Java version. Default is 11 because ShaidyMapGen.jar is compiled for Java 11.
#'
#' @return Boolean value indicating if the installed Java version meets the required version.
#'
#' @noRd
#' @keywords internal
checkForJavaVersion <- function(javaExecutable = "java", requiredJavaVersion = 11) {
requiredJavaVersion <- as.integer(requiredJavaVersion)
message <- paste0("CRITICAL WARNING: Unable to verify Java installation. ",
"Java ", requiredJavaVersion, " is required to create .ngchm and .html files.\n\n",
"\tInstall Java ", requiredJavaVersion, " or higher for to create .ngchm and .html files.\n")
checkResponse <- NULL
suppressWarnings(try({
checkResponse <- system2(javaExecutable, "--version", stdout = TRUE, stderr = TRUE)
}, silent = TRUE))
if (is.null(checkResponse)) { # java not installed
warning(message)
return(FALSE)
}
haveVersion <- FALSE
suppressWarnings(try({
versionNumber <- strsplit(checkResponse, split = "\\.")[[1]][1] # from first line , rm everything after first '.'
versionNumber <- as.numeric(gsub("\\D", "", versionNumber)) # rm non-digits, should be left with major version number
if (versionNumber >= requiredJavaVersion) {
haveVersion <- TRUE
}
}, silent = TRUE))
if (!haveVersion) { # java installed, but version is less than required (or version number could not be extracted)
warning(message)
return(FALSE)
}
return(TRUE) # java installed and version is at least required version
}

#' Check for NGCHMSupportFiles package
#'
#' If the environment variables SHAIDYMAPGEN and NGCHMWIDGETPATH are set, we assume the user has what they need.
#' If the environment variables are not set, we check if the NGCHMSupportFiles package is installed and provide
#' user feedback.
#'
#' @param None.
#'
#' @return Boolean value. TRUE if SHAIDYMAPGEN and NGCHMWIDGETPATH are set, FALSE otherwise.
#'
#' @noRd
#' @keywords internal
checkForNGCHMSupportFiles <- function() {
SHAIDYMAPGEN <- Sys.getenv("SHAIDYMAPGEN")
NGCHMWIDGETPATH <- Sys.getenv("NGCHMWIDGETPATH")
if (nzchar(SHAIDYMAPGEN) > 0 && nzchar(NGCHMWIDGETPATH) > 0) { # SHAIDYMAPGEN and NGCHMWIDGETPATH are set
return(TRUE)
}
mary <- suppressWarnings(find.package("NGCHMSupportFiles", quiet = TRUE))
if (length(suppressWarnings(find.package("NGCHMSupportFiles", quiet = TRUE))) > 0) { # NGCHMSupportFiles is installed
warning(paste0("WARNING: NGCHMSupportFiles package is installed but not loaded. ",
"This package is required to create .ngchm and .html files. ",
"Please load the package with command:\n\n",
"\tlibrary(NGCHMSupportFiles)\n"))
} else {
warning(paste0("CRITICAL WARNING: Package NGCHMSupportFiles is not installed. ",
"This package is required to create .ngchm and .html files. ",
"Please install and load NGCHMSupportFiles with commands: \n\n",
"\tinstall.packages('NGCHMSupportFiles', repos = c('https://md-anderson-bioinformatics.r-universe.dev', 'https://cloud.r-project.org'))\n\n",
"\tlibrary(NGCHMSupportFiles)\n"))
}
return(FALSE)
}

#' Check for NGCHMDemoData package
#'
#' @param None.
#'
#' @return Boolean. TRUE if NGCHMDemoData is loaded, FALSE otherwise.
#'
#' @noRd
#' @keywords internal
checkForNGCHMDemoData <- function() {
if ("package:NGCHMDemoData" %in% search()) { # NGCHMDemoData is loaded
return(TRUE)
}
if (length(suppressWarnings(find.package("NGCHMDemoData", quiet = TRUE))) > 0) { # NGCHMDemoData is installed
warning(paste0("WARNING: NGCHMDemoData package is installed but not loaded. ",
"To run examples and website vignettes, please load the package with command:\n\n",
"\tlibrary(NGCHMDemoData)\n"))
} else {
warning(paste0("NOTE: Package NGCHMDemoData is not installed. ",
"This package is used by the examples and website vignettes. Please install and load NGCHMDemoData with command: \n\n",
"\tinstall.packages('NGCHMDemoData', repos = c('https://md-anderson-bioinformatics.r-universe.dev', 'https://cloud.r-project.org'))\n\n",
"\tlibrary(NGCHMDemoData)\n"))
}
return(FALSE)
}
10 changes: 10 additions & 0 deletions R/package.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,16 @@
#' ngchmLayer, row and column dendrograms, classification bars, and popup menu entries;
#' compile and install it on an available ngchmServer.
#'
#' Note:
#' - `chmNew()` requires **git** to be installed.
#' - `chmExportToFile()`, `chmExportToHTML()`, and `chmExportToPDF()` require
#' **Java 11** and the **[NGCHMSupportFiles](https://github.com/MD-Anderson-Bioinformatics/NGCHMSupportFiles)**
#' package. The NGCHMSupportFiles package
#' can be installed with: \cr\cr
#' \code{install.packages('NGCHMDemoData', } \cr
#' \code{repos = c('https://md-anderson-bioinformatics.r-universe.dev',} \cr
#' \code{'https://cloud.r-project.org'))}
#'
#' @section Initialization:
#' When first loaded the NGCHM library reads configuration files in
#' the directories specified by the NGCHMCONFIGPATH environment variable. This is
Expand Down
7 changes: 5 additions & 2 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -490,8 +490,10 @@ loadConfigDir <- function(dirname) {
.onAttach <- function(libname, pkgname) {
getConfigDirs()

# Check if suggested system applications are available.
for (program in c("git", "java", "tar", "scp", "ssh")) testExternalProgram(program)
checkForExternalUtilities() # Check suggested utilities are installed (e.g. git, ssh, etc. Does not check for java)
checkForJavaVersion() # Check required version of java is installed
checkForNGCHMSupportFiles()
checkForNGCHMDemoData()

chmNewFunction("", "Simple reference", "")
chmNewFunction(
Expand All @@ -509,3 +511,4 @@ loadConfigDir <- function(dirname) {
loadConfigDir(file.path(cfgdir, "conf.d"))
}
}

12 changes: 12 additions & 0 deletions man/NGCHM-package.Rd

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

8 changes: 8 additions & 0 deletions man/chmExportToFile-method.Rd

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

8 changes: 8 additions & 0 deletions man/chmExportToHTML-method.Rd

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

Loading

0 comments on commit 7aac307

Please sign in to comment.