From ad91beaeb24a39ec50392ec8da8bcee58caf4b4e Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 14:18:41 -0800 Subject: [PATCH 01/88] Add journal() --- DESCRIPTION | 2 +- NAMESPACE | 3 ++ NEWS | 7 ++- R/ClusterFuture-class.R | 2 + R/ConstantFuture-class.R | 1 + R/Future-class.R | 7 ++- R/MulticoreFuture-class.R | 2 + R/journal.R | 91 +++++++++++++++++++++++++++++++++++++++ man/journal.Rd | 19 ++++++++ 9 files changed, 130 insertions(+), 4 deletions(-) create mode 100644 R/journal.R create mode 100644 man/journal.Rd diff --git a/DESCRIPTION b/DESCRIPTION index b51c14e8..a131a8ed 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.24.0-9001 +Version: 1.24.0-9002 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NAMESPACE b/NAMESPACE index e6c7658d..13fe3323 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -16,6 +16,7 @@ S3method(getExpression,Future) S3method(getExpression,MulticoreFuture) S3method(getExpression,MultisessionFuture) S3method(getExpression,UniprocessFuture) +S3method(journal,Future) S3method(mandelbrot,matrix) S3method(mandelbrot,numeric) S3method(nbrOfFreeWorkers,"NULL") @@ -33,6 +34,7 @@ S3method(nbrOfWorkers,uniprocess) S3method(plot,Mandelbrot) S3method(print,Future) S3method(print,FutureCondition) +S3method(print,FutureJournal) S3method(print,FutureResult) S3method(print,FutureStrategy) S3method(print,FutureStrategyList) @@ -117,6 +119,7 @@ export(futureSessionInfo) export(futures) export(getExpression) export(getGlobalsAndPackages) +export(journal) export(makeClusterMPI) export(makeClusterPSOCK) export(makeNodePSOCK) diff --git a/NEWS b/NEWS index 0712aaec..97956b47 100644 --- a/NEWS +++ b/NEWS @@ -1,12 +1,17 @@ Package: future =============== -Version: 1.24.0-9001 [2022-02-23] +Version: 1.24.0-9002 [2022-02-25] SIGNIFICANT CHANGES: * R options and environment variables are now reset on the workers after future is resolved so that any changes to them have no effect later on. + +BETA FEATURES: + + * Add journal() for retrieving timing information of internal events for + a specific future. Version: 1.24.0 [2022-02-19] diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 030281f7..4575600c 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -52,6 +52,8 @@ ClusterFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame() future <- do.call(MultiprocessFuture, args = c(list(expr = quote(expr), substitute = FALSE, envir = envir, globals = globals, packages = packages, local = local, node = NA_integer_, persistent = persistent), args[future_args]), quote = FALSE) future <- do.call(as_ClusterFuture, args = c(list(future, workers = workers), args[!future_args]), quote = TRUE) + + updateFutureJournal(future, "create") future } diff --git a/R/ConstantFuture-class.R b/R/ConstantFuture-class.R index d901f08a..698b1553 100644 --- a/R/ConstantFuture-class.R +++ b/R/ConstantFuture-class.R @@ -15,6 +15,7 @@ ConstantFuture <- function(..., globals = TRUE, envir = emptyenv()) { future$result <- FutureResult(value = eval(future$expr, envir = envir)) future$state <- "finished" future <- structure(future, class = c("ConstantFuture", class(future))) + updateFutureJournal(future, "create") future } diff --git a/R/Future-class.R b/R/Future-class.R index f082ea2b..00068c4e 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -93,7 +93,8 @@ #' @name Future-class Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdout = TRUE, conditions = "condition", globals = NULL, packages = NULL, seed = FALSE, lazy = FALSE, local = TRUE, gc = FALSE, earlySignal = FALSE, label = NULL, ...) { if (substitute) expr <- substitute(expr) - + t_start <- Sys.time() + if (is.null(seed)) { } else if (isFALSE(seed)) { } else if (is_lecyer_cmrg_seed(seed)) { @@ -178,7 +179,9 @@ Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdou .Defunct(msg = "Future field 'value' is defunct and must not be set", package = .packageName) } - structure(core, class = c("Future", class(core))) + future <- structure(core, class = c("Future", class(core))) + future <- makeFutureJournal(future, start = t_start) + future } diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index b9f2061b..13cc4b58 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -41,6 +41,8 @@ MulticoreFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame future <- as_MulticoreFuture(future, ...) + updateFutureJournal(future, "create") + future } diff --git a/R/journal.R b/R/journal.R new file mode 100644 index 00000000..9e77cfa1 --- /dev/null +++ b/R/journal.R @@ -0,0 +1,91 @@ +#' Gets a journal of events for a future +#' +#' @param x A [Future] object. +#' +#' @param \ldots Not used. +#' +#' @return +#' A data frame with columns `step`, `start`, `stop`, and `duration`.a +#' +#' @export +journal <- function(x, ...) UseMethod("journal") + +#' @export +journal.Future <- function(x, ...) { + data <- x$.journal + stop_if_not(inherits(data, "FutureJournal")) + + ## Backward compatibility (until all backends does this) + if (!is.element("evaluate", data$step) && !is.null(x$result)) { + x <- appendToFutureJournal(x, + step = "evaluate", + start = x$result$started, + stop = x$result$finished + ) + data <- x$.journal + stop_if_not(inherits(data, "FutureJournal")) + } + + data +} + +#' @export +print.FutureJournal <- function(x, digits.secs = 3L, ...) { + oopts <- options(digits.secs = digits.secs) + on.exit(options(oopts)) + NextMethod("print") +} + + +makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time()) { + stop_if_not( + inherits(x, "Future"), + length(step) == 1L, is.character(step), + length(start) == 1L, inherits(start, "POSIXct"), + length(stop) == 1L, inherits(stop, "POSIXct") + ) + + data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + class(data) <- c("FutureJournal", class(data)) + x$.journal <- data + invisible(x) +} + + +updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { + stop_if_not( + inherits(x, "Future"), + length(step) == 1L, is.character(step), + is.null(start) || (length(start) == 1L && inherits(start, "POSIXct")), + is.null(stop) || (length(stop) == 1L && inherits(stop, "POSIXct")) + ) + + data <- x$.journal + stop_if_not(inherits(data, "FutureJournal")) + row <- which(data$step == step) + n <- length(row) + if (n == 0L) stop("No such 'step' entry in journal: ", sQuote(step)) + if (n > 1L) row <- row[n] + entry <- data[row, ] + if (!is.null(start)) entry$start <- start + if (!is.null(stop)) entry$stop <- stop + entry$duration <- entry$stop - entry$start + data[row, ] <- entry + stop_if_not(inherits(data, "FutureJournal")) + x$.journal <- data + invisible(x) +} + + +appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct(NA_real_)) { + stop_if_not( + inherits(x, "Future"), + length(step) == 1L, is.character(step), + length(start) == 1L, inherits(start, "POSIXct"), + length(stop) == 1L, inherits(stop, "POSIXct") + ) + + data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + x$.journal <- rbind(x$.journal, data) + invisible(x) +} diff --git a/man/journal.Rd b/man/journal.Rd new file mode 100644 index 00000000..a28763f9 --- /dev/null +++ b/man/journal.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/journal.R +\name{journal} +\alias{journal} +\title{Gets a journal of events for a future} +\usage{ +journal(x, ...) +} +\arguments{ +\item{x}{A \link{Future} object.} + +\item{\ldots}{Not used.} +} +\value{ +A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}.a +} +\description{ +Gets a journal of events for a future +} From 8db5e2f54b2dd240d4ea7da554f5214c191e4ab7 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 14:41:00 -0800 Subject: [PATCH 02/88] Now future(), and generic functions run(), resolved(), and result() gather journal stats for Future objects --- R/ClusterFuture-class.R | 2 -- R/ConstantFuture-class.R | 1 - R/Future-class.R | 36 +++++++++++++++++++++++++++++++----- R/MulticoreFuture-class.R | 2 -- R/future.R | 5 ++++- R/journal.R | 15 ++++++++++++--- R/resolved.R | 16 +++++++++++++++- man/journal.Rd | 2 +- 8 files changed, 63 insertions(+), 16 deletions(-) diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 4575600c..bd7491fe 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -53,8 +53,6 @@ ClusterFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame() future <- do.call(as_ClusterFuture, args = c(list(future, workers = workers), args[!future_args]), quote = TRUE) - updateFutureJournal(future, "create") - future } diff --git a/R/ConstantFuture-class.R b/R/ConstantFuture-class.R index 698b1553..d901f08a 100644 --- a/R/ConstantFuture-class.R +++ b/R/ConstantFuture-class.R @@ -15,7 +15,6 @@ ConstantFuture <- function(..., globals = TRUE, envir = emptyenv()) { future$result <- FutureResult(value = eval(future$expr, envir = envir)) future$state <- "finished" future <- structure(future, class = c("ConstantFuture", class(future))) - updateFutureJournal(future, "create") future } diff --git a/R/Future-class.R b/R/Future-class.R index 00068c4e..43725602 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -179,9 +179,7 @@ Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdou .Defunct(msg = "Future field 'value' is defunct and must not be set", package = .packageName) } - future <- structure(core, class = c("Future", class(core))) - future <- makeFutureJournal(future, start = t_start) - future + structure(core, class = c("Future", class(core))) } @@ -446,12 +444,40 @@ run.Future <- function(future, ...) { future } -run <- function(...) UseMethod("run") +#' @export +#' @keywords internal +run <- function(future, ...) { + ## Automatically update journal entries for Future object + if (inherits(future, "Future")) { + start <- Sys.time() + on.exit({ + appendToFutureJournal(future, + step = "launch", + start = start, + stop = Sys.time() + ) + }) + } + UseMethod("run") +} #' @export #' @keywords internal -result <- function(...) UseMethod("result") +result <- function(future, ...) { + ## Automatically update journal entries for Future object + if (inherits(future, "Future")) { + start <- Sys.time() + on.exit({ + appendToFutureJournal(future, + step = "gather", + start = start, + stop = Sys.time() + ) + }) + } + UseMethod("result") +} #' Get the results of a resolved future #' diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index 13cc4b58..b9f2061b 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -41,8 +41,6 @@ MulticoreFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame future <- as_MulticoreFuture(future, ...) - updateFutureJournal(future, "create") - future } diff --git a/R/future.R b/R/future.R index 1aeff3bd..69c43653 100644 --- a/R/future.R +++ b/R/future.R @@ -188,6 +188,7 @@ #' @name future future <- function(expr, envir = parent.frame(), substitute = TRUE, lazy = FALSE, seed = FALSE, globals = TRUE, packages = NULL, stdout = TRUE, conditions = "condition", earlySignal = FALSE, label = NULL, gc = FALSE, ...) { if (substitute) expr <- substitute(expr) + t_start <- Sys.time() gp <- getGlobalsAndPackages(expr, envir = envir, tweak = tweakExpression, globals = globals) expr <- gp$expr @@ -216,13 +217,15 @@ future <- function(expr, envir = parent.frame(), substitute = TRUE, lazy = FALSE ## Comment: Only allowed for persistent 'cluster' futures future$.defaultLocal <- !is.element("local", names(list(...))) + future <- makeFutureJournal(future, start = t_start) + if (!lazy) { future <- run(future) future$lazy <- FALSE ## Assert that a future was returned stop_if_not(inherits(future, "Future"), !future$lazy) } - + future } diff --git a/R/journal.R b/R/journal.R index 9e77cfa1..95e622dd 100644 --- a/R/journal.R +++ b/R/journal.R @@ -5,7 +5,7 @@ #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step`, `start`, `stop`, and `duration`.a +#' A data frame with columns `step`, `start`, `stop`, and `duration`. #' #' @export journal <- function(x, ...) UseMethod("journal") @@ -40,6 +40,7 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time()) { stop_if_not( inherits(x, "Future"), + is.null(x$.journal), length(step) == 1L, is.character(step), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") @@ -53,6 +54,9 @@ makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time( updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { + ## Nothing to do? + if (!inherits(x$.journal, "FutureJournal")) return(x) + stop_if_not( inherits(x, "Future"), length(step) == 1L, is.character(step), @@ -77,14 +81,19 @@ updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { } -appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct(NA_real_)) { +appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { + ## Nothing to do? + if (!inherits(x$.journal, "FutureJournal")) return(x) + + if (skip && is.element(step, x$.journal$step)) return(x) + stop_if_not( inherits(x, "Future"), length(step) == 1L, is.character(step), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - + data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) x$.journal <- rbind(x$.journal, data) invisible(x) diff --git a/R/resolved.R b/R/resolved.R index 5ecdb77c..c93bb3f5 100644 --- a/R/resolved.R +++ b/R/resolved.R @@ -19,7 +19,21 @@ #' e.g. `while (!resolved(future)) Sys.sleep(5)`. #' #' @export -resolved <- function(x, ...) UseMethod("resolved") +resolved <- function(x, ...) { + ## Automatically update journal entries for Future object + if (inherits(x, "Future")) { + start <- Sys.time() + on.exit({ + appendToFutureJournal(x, + step = "resolved", + start = start, + stop = Sys.time(), + skip = FALSE + ) + }) + } + UseMethod("resolved") +} #' @export resolved.default <- function(x, ...) TRUE diff --git a/man/journal.Rd b/man/journal.Rd index a28763f9..059aa29a 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,7 +12,7 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}.a +A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}. } \description{ Gets a journal of events for a future From 2a19a451e6a370a24577295fb79872b33b52db95 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 15:48:38 -0800 Subject: [PATCH 03/88] journal(): Sort by 'start' --- R/journal.R | 3 +++ 1 file changed, 3 insertions(+) diff --git a/R/journal.R b/R/journal.R index 95e622dd..eb1b2e38 100644 --- a/R/journal.R +++ b/R/journal.R @@ -26,6 +26,9 @@ journal.Future <- function(x, ...) { stop_if_not(inherits(data, "FutureJournal")) } + ## Sort by start time + if (nrow(data) > 1L) data <- data[order(data$start), ] + data } From 36f415d54ebc14cf49a29dccf68afab78b27f1fe Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 16:04:24 -0800 Subject: [PATCH 04/88] journal(): calculate relative start time (at) and duration on the fly --- R/journal.R | 19 ++++++++++++++----- man/journal.Rd | 7 ++++++- 2 files changed, 20 insertions(+), 6 deletions(-) diff --git a/R/journal.R b/R/journal.R index eb1b2e38..ce5f9c59 100644 --- a/R/journal.R +++ b/R/journal.R @@ -5,7 +5,12 @@ #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step`, `start`, `stop`, and `duration`. +#' A data frame with columns `step`, `start`, `stop`, `at`, and `duration`, +#' where the latter two are calculated from `start` and `stop`. +#' The data frame is sorted by the `start` time. +#' Note that the timestamps for the `evaluate` step are based on the local +#' time on the worker. The system clocks on the worker and the calling R +#' system may be out of sync. #' #' @export journal <- function(x, ...) UseMethod("journal") @@ -27,7 +32,12 @@ journal.Future <- function(x, ...) { } ## Sort by start time - if (nrow(data) > 1L) data <- data[order(data$start), ] + n <- nrow(data) + if (n > 1L) data <- data[order(data$start), ] + + ## Append 'at' and 'duration' + data$at <- data$start - data$start[1] + data$duration <- data$stop - data$start data } @@ -49,7 +59,7 @@ makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time( length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + data <- data.frame(step = step, start = start, stop = stop) class(data) <- c("FutureJournal", class(data)) x$.journal <- data invisible(x) @@ -76,7 +86,6 @@ updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { entry <- data[row, ] if (!is.null(start)) entry$start <- start if (!is.null(stop)) entry$stop <- stop - entry$duration <- entry$stop - entry$start data[row, ] <- entry stop_if_not(inherits(data, "FutureJournal")) x$.journal <- data @@ -97,7 +106,7 @@ appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + data <- data.frame(step = step, start = start, stop = stop) x$.journal <- rbind(x$.journal, data) invisible(x) } diff --git a/man/journal.Rd b/man/journal.Rd index 059aa29a..aa304660 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,7 +12,12 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}. +A data frame with columns \code{step}, \code{start}, \code{stop}, \code{at}, and \code{duration}, +where the latter two are calculated from \code{start} and \code{stop}. +The data frame is sorted by the \code{start} time. +Note that the timestamps for the \code{evaluate} step are based on the local +time on the worker. The system clocks on the worker and the calling R +system may be out of sync. } \description{ Gets a journal of events for a future From b39ca26b50608e5fa51dd0997f38f10c9996b25d Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sat, 26 Feb 2022 21:01:58 -0800 Subject: [PATCH 05/88] Avoid exporting journal() for now; it'll be under heavy development for quite some time --- NAMESPACE | 1 - NEWS | 7 ++++--- R/journal.R | 30 +++++++++++++++++++----------- incl/journal.R | 12 ++++++++++++ man/journal.Rd | 20 +++++++++++++++++--- 5 files changed, 52 insertions(+), 18 deletions(-) create mode 100644 incl/journal.R diff --git a/NAMESPACE b/NAMESPACE index 13fe3323..a0d709d8 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -119,7 +119,6 @@ export(futureSessionInfo) export(futures) export(getExpression) export(getGlobalsAndPackages) -export(journal) export(makeClusterMPI) export(makeClusterPSOCK) export(makeNodePSOCK) diff --git a/NEWS b/NEWS index 97956b47..9434f6ef 100644 --- a/NEWS +++ b/NEWS @@ -1,7 +1,7 @@ Package: future =============== -Version: 1.24.0-9002 [2022-02-25] +Version: 1.24.0-9002 [2022-02-26] SIGNIFICANT CHANGES: @@ -10,8 +10,9 @@ SIGNIFICANT CHANGES: BETA FEATURES: - * Add journal() for retrieving timing information of internal events for - a specific future. + * Add internal journal() for retrieving timing information of internal + events for a specific future. This function is non-exported for now, + because it is under development. Please do _not_ use it in a package. Version: 1.24.0 [2022-02-19] diff --git a/R/journal.R b/R/journal.R index ce5f9c59..955b50ae 100644 --- a/R/journal.R +++ b/R/journal.R @@ -2,23 +2,30 @@ #' #' @param x A [Future] object. #' +## @param baseline (POSIXct; optional) A baseline timestamp that the +## relative start time (`at`) should be calculated towards. The default +## is the first `start` time in the journal. +#' #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step`, `start`, `stop`, `at`, and `duration`, -#' where the latter two are calculated from `start` and `stop`. -#' The data frame is sorted by the `start` time. +#' A data frame with columns `step` (character string), `start` (POSIXct), +#' `at` (difftime), and `duration` (difftime). +#' The data frame is sorted by the `at` time. #' Note that the timestamps for the `evaluate` step are based on the local #' time on the worker. The system clocks on the worker and the calling R #' system may be out of sync. #' -#' @export +#' @example incl/journal.R journal <- function(x, ...) UseMethod("journal") #' @export -journal.Future <- function(x, ...) { +journal.Future <- function(x, baseline = NULL, ...) { data <- x$.journal - stop_if_not(inherits(data, "FutureJournal")) + stop_if_not( + inherits(data, "FutureJournal"), + is.null(baseline) || (length(baseline) == 1L && inherits(baseline, "POSIXct")) + ) ## Backward compatibility (until all backends does this) if (!is.element("evaluate", data$step) && !is.null(x$result)) { @@ -31,13 +38,14 @@ journal.Future <- function(x, ...) { stop_if_not(inherits(data, "FutureJournal")) } - ## Sort by start time - n <- nrow(data) - if (n > 1L) data <- data[order(data$start), ] - ## Append 'at' and 'duration' - data$at <- data$start - data$start[1] + if (is.null(baseline)) baseline <- data$start[1] + data$at <- data$start - baseline data$duration <- data$stop - data$start + data$stop <- NULL + + ## Sort by relative start time + if (nrow(data) > 1L) data <- data[order(data$at), ] data } diff --git a/incl/journal.R b/incl/journal.R new file mode 100644 index 00000000..13ad71e0 --- /dev/null +++ b/incl/journal.R @@ -0,0 +1,12 @@ +library(future) +journal <- future:::journal +plan(multisession, workers = 2L) + +t_start <- Sys.time() +fs <- lapply(1:3, FUN = function(x) future({ Sys.sleep(x); sqrt(x) })) +vs <- value(fs) +js <- lapply(fs, FUN = journal, baseline = t_start) +print(js) + +## Stop parallel workers +plan(sequential) diff --git a/man/journal.Rd b/man/journal.Rd index aa304660..7e0274fd 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,9 +12,9 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step}, \code{start}, \code{stop}, \code{at}, and \code{duration}, -where the latter two are calculated from \code{start} and \code{stop}. -The data frame is sorted by the \code{start} time. +A data frame with columns \code{step} (character string), \code{start} (POSIXct), +\code{at} (difftime), and \code{duration} (difftime). +The data frame is sorted by the \code{at} time. Note that the timestamps for the \code{evaluate} step are based on the local time on the worker. The system clocks on the worker and the calling R system may be out of sync. @@ -22,3 +22,17 @@ system may be out of sync. \description{ Gets a journal of events for a future } +\examples{ +library(future) +journal <- future:::journal +plan(multisession, workers = 2L) + +t_start <- Sys.time() +fs <- lapply(1:3, FUN = function(x) future({ Sys.sleep(x); sqrt(x) })) +vs <- value(fs) +js <- lapply(fs, FUN = journal, baseline = t_start) +print(js) + +## Stop parallel workers +plan(sequential) +} From 03a366bbdd5dab9d2af0b2fc3b478eef184f841a Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sat, 26 Feb 2022 21:31:39 -0800 Subject: [PATCH 06/88] Now FutureResult objects hold the session UUID of the worker. journal() returns also the future label and the UUID. It also return the session UUID, which is either the calling session or the worker session (for the 'evaluation' step). --- NEWS | 2 ++ R/FutureResult-class.R | 19 ++++++++++--------- R/journal.R | 25 +++++++++++++++++++++++-- 3 files changed, 35 insertions(+), 11 deletions(-) diff --git a/NEWS b/NEWS index 9434f6ef..66becc86 100644 --- a/NEWS +++ b/NEWS @@ -8,6 +8,8 @@ SIGNIFICANT CHANGES: * R options and environment variables are now reset on the workers after future is resolved so that any changes to them have no effect later on. + * Now FutureResult objects hold the session UUID of the worker. + BETA FEATURES: * Add internal journal() for retrieving timing information of internal diff --git a/R/FutureResult-class.R b/R/FutureResult-class.R index ddd68980..16a143d7 100644 --- a/R/FutureResult-class.R +++ b/R/FutureResult-class.R @@ -71,16 +71,17 @@ FutureResult <- local({ } structure(list( - value = value, - visible = visible, - stdout = stdout, - conditions = conditions, - rng = rng, + value = value, + visible = visible, + stdout = stdout, + conditions = conditions, + rng = rng, ..., - started = started, - finished = finished, - r_info = r_info, - version = version + started = started, + finished = finished, + session_uuid = session_uuid(), + r_info = r_info, + version = version ), class = "FutureResult") } }) diff --git a/R/journal.R b/R/journal.R index 955b50ae..2b9ddc3c 100644 --- a/R/journal.R +++ b/R/journal.R @@ -9,8 +9,16 @@ #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step` (character string), `start` (POSIXct), -#' `at` (difftime), and `duration` (difftime). +#' A data frame with columns: +#' +#' 1. `step` (character string) +#' 2. `start` (POSIXct) +#' 3. `at` (difftime) +#' 4. `duration` (difftime) +#' 5. `future_label` (character string) +#' 6. `future_uuid` (character string) +#' 7. `session_uuid` (character string) +#' #' The data frame is sorted by the `at` time. #' Note that the timestamps for the `evaluate` step are based on the local #' time on the worker. The system clocks on the worker and the calling R @@ -26,15 +34,19 @@ journal.Future <- function(x, baseline = NULL, ...) { inherits(data, "FutureJournal"), is.null(baseline) || (length(baseline) == 1L && inherits(baseline, "POSIXct")) ) + + session_uuid <- rep(x$owner, times = nrow(data)) ## Backward compatibility (until all backends does this) if (!is.element("evaluate", data$step) && !is.null(x$result)) { + stop_if_not(is.character(session_uuid)) x <- appendToFutureJournal(x, step = "evaluate", start = x$result$started, stop = x$result$finished ) data <- x$.journal + session_uuid <- c(session_uuid, x$result$session_uuid) stop_if_not(inherits(data, "FutureJournal")) } @@ -44,6 +56,15 @@ journal.Future <- function(x, baseline = NULL, ...) { data$duration <- data$stop - data$start data$stop <- NULL + ## Append future 'label' + data$future_label <- if (is.null(x$label)) NA_character_ else x$label + + ## Append future UUID + data$future_uuid <- x$uuid + + ## Append session UUID + data$session_uuid <- session_uuid + ## Sort by relative start time if (nrow(data) > 1L) data <- data[order(data$at), ] From 60f40cb7321d3fe24b6d6fa97af4c19a998482c3 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 28 Feb 2022 15:49:31 -0800 Subject: [PATCH 07/88] Add journal() for lists (of Future:s or FutureJournal:s) and for FutureJournal (to change 'baseline') --- NAMESPACE | 2 ++ R/journal.R | 22 ++++++++++++++++++++++ man/journal.Rd | 13 +++++++++++-- 3 files changed, 35 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index a0d709d8..8ae3f9ec 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -17,6 +17,8 @@ S3method(getExpression,MulticoreFuture) S3method(getExpression,MultisessionFuture) S3method(getExpression,UniprocessFuture) S3method(journal,Future) +S3method(journal,FutureJournal) +S3method(journal,list) S3method(mandelbrot,matrix) S3method(mandelbrot,numeric) S3method(nbrOfFreeWorkers,"NULL") diff --git a/R/journal.R b/R/journal.R index 2b9ddc3c..07558336 100644 --- a/R/journal.R +++ b/R/journal.R @@ -71,6 +71,28 @@ journal.Future <- function(x, baseline = NULL, ...) { data } +#' @export +journal.FutureJournal <- function(x, baseline = NULL, ...) { + if (!is.null(baseline)) { + x$at <- x$at - baseline + } + x +} + +#' @export +journal.list <- function(x, index = seq_along(x), ...) { + if (!is.null(index)) { + stop_if_not(length(index) == length(x)) + x <- lapply(index, FUN = function(idx) { + journal <- journal(x[[idx]], ...) + stop_if_not(inherits(journal, "FutureJournal")) + cbind(index = idx, journal) + }) + } + Reduce(rbind, x) +} + + #' @export print.FutureJournal <- function(x, digits.secs = 3L, ...) { oopts <- options(digits.secs = digits.secs) diff --git a/man/journal.Rd b/man/journal.Rd index 7e0274fd..a73ccf0f 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,8 +12,17 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step} (character string), \code{start} (POSIXct), -\code{at} (difftime), and \code{duration} (difftime). +A data frame with columns: +\enumerate{ +\item \code{step} (character string) +\item \code{start} (POSIXct) +\item \code{at} (difftime) +\item \code{duration} (difftime) +\item \code{future_label} (character string) +\item \code{future_uuid} (character string) +\item \code{session_uuid} (character string) +} + The data frame is sorted by the \code{at} time. Note that the timestamps for the \code{evaluate} step are based on the local time on the worker. The system clocks on the worker and the calling R From e8e04c110ba987b969b40ed1dbb92894df223fd5 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 28 Feb 2022 18:20:24 -0800 Subject: [PATCH 08/88] journal(..., baseline = TRUE) for futures/journals now sets the zero-time relative start time to the minimal observed timestamp --- R/journal.R | 44 ++++++++++++++++++++++++++++---------------- 1 file changed, 28 insertions(+), 16 deletions(-) diff --git a/R/journal.R b/R/journal.R index 07558336..24ccc3e4 100644 --- a/R/journal.R +++ b/R/journal.R @@ -2,9 +2,9 @@ #' #' @param x A [Future] object. #' -## @param baseline (POSIXct; optional) A baseline timestamp that the -## relative start time (`at`) should be calculated towards. The default -## is the first `start` time in the journal. +## @param baseline (POSIXct; optional) A timestamp to server as time zero +## for the relative start time (`at`). If `TRUE` (default), then the +## earliest timepoint observed is used as the baseline. #' #' @param \ldots Not used. #' @@ -28,12 +28,9 @@ journal <- function(x, ...) UseMethod("journal") #' @export -journal.Future <- function(x, baseline = NULL, ...) { +journal.Future <- function(x, ...) { data <- x$.journal - stop_if_not( - inherits(data, "FutureJournal"), - is.null(baseline) || (length(baseline) == 1L && inherits(baseline, "POSIXct")) - ) + stop_if_not(inherits(data, "FutureJournal")) session_uuid <- rep(x$owner, times = nrow(data)) @@ -50,8 +47,10 @@ journal.Future <- function(x, baseline = NULL, ...) { stop_if_not(inherits(data, "FutureJournal")) } + ## Find relative time zero + baseline <- min(data$start, na.rm = TRUE) + ## Append 'at' and 'duration' - if (is.null(baseline)) baseline <- data$start[1] data$at <- data$start - baseline data$duration <- data$stop - data$start data$stop <- NULL @@ -73,23 +72,36 @@ journal.Future <- function(x, baseline = NULL, ...) { #' @export journal.FutureJournal <- function(x, baseline = NULL, ...) { + ## Reset relative time zero? if (!is.null(baseline)) { - x$at <- x$at - baseline + if (isTRUE(baseline)) baseline <- min(x$start, na.rm = TRUE) + x$at <- x$start - baseline } x } #' @export -journal.list <- function(x, index = seq_along(x), ...) { +journal.list <- function(x, index = seq_along(x), baseline = TRUE, ...) { + ## Reset relative time zero to the first observed timestamp? + if (isTRUE(baseline)) { + stop_if_not(baseline >= 1L, baseline <= length(x)) + x <- lapply(x, FUN = journal, ...) + start <- lapply(x, FUN = function(x) min(x$start, na.rm = TRUE)) + start <- Reduce(c, start) + baseline <- min(start, na.rm = TRUE) + } + + js <- lapply(x, FUN = journal, baseline = baseline, ...) + + ## Add index? if (!is.null(index)) { stop_if_not(length(index) == length(x)) - x <- lapply(index, FUN = function(idx) { - journal <- journal(x[[idx]], ...) - stop_if_not(inherits(journal, "FutureJournal")) - cbind(index = idx, journal) + js <- lapply(index, FUN = function(idx) { + cbind(index = idx, js[[idx]]) }) } - Reduce(rbind, x) + + Reduce(rbind, js) } From 107a7901805c38f6d73dfbb79394556bc48bddf5 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 14:18:41 -0800 Subject: [PATCH 09/88] Add journal() --- DESCRIPTION | 2 +- NAMESPACE | 3 ++ NEWS | 7 ++- R/ClusterFuture-class.R | 2 + R/ConstantFuture-class.R | 1 + R/Future-class.R | 7 ++- R/MulticoreFuture-class.R | 2 + R/journal.R | 91 +++++++++++++++++++++++++++++++++++++++ man/journal.Rd | 19 ++++++++ 9 files changed, 130 insertions(+), 4 deletions(-) create mode 100644 R/journal.R create mode 100644 man/journal.Rd diff --git a/DESCRIPTION b/DESCRIPTION index b51c14e8..a131a8ed 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.24.0-9001 +Version: 1.24.0-9002 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NAMESPACE b/NAMESPACE index e6c7658d..13fe3323 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -16,6 +16,7 @@ S3method(getExpression,Future) S3method(getExpression,MulticoreFuture) S3method(getExpression,MultisessionFuture) S3method(getExpression,UniprocessFuture) +S3method(journal,Future) S3method(mandelbrot,matrix) S3method(mandelbrot,numeric) S3method(nbrOfFreeWorkers,"NULL") @@ -33,6 +34,7 @@ S3method(nbrOfWorkers,uniprocess) S3method(plot,Mandelbrot) S3method(print,Future) S3method(print,FutureCondition) +S3method(print,FutureJournal) S3method(print,FutureResult) S3method(print,FutureStrategy) S3method(print,FutureStrategyList) @@ -117,6 +119,7 @@ export(futureSessionInfo) export(futures) export(getExpression) export(getGlobalsAndPackages) +export(journal) export(makeClusterMPI) export(makeClusterPSOCK) export(makeNodePSOCK) diff --git a/NEWS b/NEWS index ac59d929..5f5703e7 100644 --- a/NEWS +++ b/NEWS @@ -1,7 +1,7 @@ Package: future =============== -Version: 1.24.0-9001 [2022-02-28] +Version: 1.24.0-9002 [2022-02-28] SIGNIFICANT CHANGES: @@ -14,6 +14,11 @@ PERFORMANCE: can be overridden by an R option, cf. help("future.options"). Now resolve() respects this option (previously it was hardcoded to 0.1 seconds). +BETA FEATURES: + + * Add journal() for retrieving timing information of internal events for + a specific future. + Version: 1.24.0 [2022-02-19] diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index ed1fe844..d4f5485e 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -52,6 +52,8 @@ ClusterFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame() future <- do.call(MultiprocessFuture, args = c(list(expr = quote(expr), substitute = FALSE, envir = envir, globals = globals, packages = packages, local = local, node = NA_integer_, persistent = persistent), args[future_args]), quote = FALSE) future <- do.call(as_ClusterFuture, args = c(list(future, workers = workers), args[!future_args]), quote = TRUE) + + updateFutureJournal(future, "create") future } diff --git a/R/ConstantFuture-class.R b/R/ConstantFuture-class.R index d901f08a..698b1553 100644 --- a/R/ConstantFuture-class.R +++ b/R/ConstantFuture-class.R @@ -15,6 +15,7 @@ ConstantFuture <- function(..., globals = TRUE, envir = emptyenv()) { future$result <- FutureResult(value = eval(future$expr, envir = envir)) future$state <- "finished" future <- structure(future, class = c("ConstantFuture", class(future))) + updateFutureJournal(future, "create") future } diff --git a/R/Future-class.R b/R/Future-class.R index f082ea2b..00068c4e 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -93,7 +93,8 @@ #' @name Future-class Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdout = TRUE, conditions = "condition", globals = NULL, packages = NULL, seed = FALSE, lazy = FALSE, local = TRUE, gc = FALSE, earlySignal = FALSE, label = NULL, ...) { if (substitute) expr <- substitute(expr) - + t_start <- Sys.time() + if (is.null(seed)) { } else if (isFALSE(seed)) { } else if (is_lecyer_cmrg_seed(seed)) { @@ -178,7 +179,9 @@ Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdou .Defunct(msg = "Future field 'value' is defunct and must not be set", package = .packageName) } - structure(core, class = c("Future", class(core))) + future <- structure(core, class = c("Future", class(core))) + future <- makeFutureJournal(future, start = t_start) + future } diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index b9f2061b..13cc4b58 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -41,6 +41,8 @@ MulticoreFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame future <- as_MulticoreFuture(future, ...) + updateFutureJournal(future, "create") + future } diff --git a/R/journal.R b/R/journal.R new file mode 100644 index 00000000..9e77cfa1 --- /dev/null +++ b/R/journal.R @@ -0,0 +1,91 @@ +#' Gets a journal of events for a future +#' +#' @param x A [Future] object. +#' +#' @param \ldots Not used. +#' +#' @return +#' A data frame with columns `step`, `start`, `stop`, and `duration`.a +#' +#' @export +journal <- function(x, ...) UseMethod("journal") + +#' @export +journal.Future <- function(x, ...) { + data <- x$.journal + stop_if_not(inherits(data, "FutureJournal")) + + ## Backward compatibility (until all backends does this) + if (!is.element("evaluate", data$step) && !is.null(x$result)) { + x <- appendToFutureJournal(x, + step = "evaluate", + start = x$result$started, + stop = x$result$finished + ) + data <- x$.journal + stop_if_not(inherits(data, "FutureJournal")) + } + + data +} + +#' @export +print.FutureJournal <- function(x, digits.secs = 3L, ...) { + oopts <- options(digits.secs = digits.secs) + on.exit(options(oopts)) + NextMethod("print") +} + + +makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time()) { + stop_if_not( + inherits(x, "Future"), + length(step) == 1L, is.character(step), + length(start) == 1L, inherits(start, "POSIXct"), + length(stop) == 1L, inherits(stop, "POSIXct") + ) + + data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + class(data) <- c("FutureJournal", class(data)) + x$.journal <- data + invisible(x) +} + + +updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { + stop_if_not( + inherits(x, "Future"), + length(step) == 1L, is.character(step), + is.null(start) || (length(start) == 1L && inherits(start, "POSIXct")), + is.null(stop) || (length(stop) == 1L && inherits(stop, "POSIXct")) + ) + + data <- x$.journal + stop_if_not(inherits(data, "FutureJournal")) + row <- which(data$step == step) + n <- length(row) + if (n == 0L) stop("No such 'step' entry in journal: ", sQuote(step)) + if (n > 1L) row <- row[n] + entry <- data[row, ] + if (!is.null(start)) entry$start <- start + if (!is.null(stop)) entry$stop <- stop + entry$duration <- entry$stop - entry$start + data[row, ] <- entry + stop_if_not(inherits(data, "FutureJournal")) + x$.journal <- data + invisible(x) +} + + +appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct(NA_real_)) { + stop_if_not( + inherits(x, "Future"), + length(step) == 1L, is.character(step), + length(start) == 1L, inherits(start, "POSIXct"), + length(stop) == 1L, inherits(stop, "POSIXct") + ) + + data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + x$.journal <- rbind(x$.journal, data) + invisible(x) +} diff --git a/man/journal.Rd b/man/journal.Rd new file mode 100644 index 00000000..a28763f9 --- /dev/null +++ b/man/journal.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/journal.R +\name{journal} +\alias{journal} +\title{Gets a journal of events for a future} +\usage{ +journal(x, ...) +} +\arguments{ +\item{x}{A \link{Future} object.} + +\item{\ldots}{Not used.} +} +\value{ +A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}.a +} +\description{ +Gets a journal of events for a future +} From 23cd3bdc16c68ca21776340694f6ef50870ffc20 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 14:41:00 -0800 Subject: [PATCH 10/88] Now future(), and generic functions run(), resolved(), and result() gather journal stats for Future objects --- R/ClusterFuture-class.R | 2 -- R/ConstantFuture-class.R | 1 - R/Future-class.R | 36 +++++++++++++++++++++++++++++++----- R/MulticoreFuture-class.R | 2 -- R/future.R | 5 ++++- R/journal.R | 15 ++++++++++++--- R/resolved.R | 16 +++++++++++++++- man/journal.Rd | 2 +- 8 files changed, 63 insertions(+), 16 deletions(-) diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index d4f5485e..b2a66975 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -53,8 +53,6 @@ ClusterFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame() future <- do.call(as_ClusterFuture, args = c(list(future, workers = workers), args[!future_args]), quote = TRUE) - updateFutureJournal(future, "create") - future } diff --git a/R/ConstantFuture-class.R b/R/ConstantFuture-class.R index 698b1553..d901f08a 100644 --- a/R/ConstantFuture-class.R +++ b/R/ConstantFuture-class.R @@ -15,7 +15,6 @@ ConstantFuture <- function(..., globals = TRUE, envir = emptyenv()) { future$result <- FutureResult(value = eval(future$expr, envir = envir)) future$state <- "finished" future <- structure(future, class = c("ConstantFuture", class(future))) - updateFutureJournal(future, "create") future } diff --git a/R/Future-class.R b/R/Future-class.R index 00068c4e..43725602 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -179,9 +179,7 @@ Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdou .Defunct(msg = "Future field 'value' is defunct and must not be set", package = .packageName) } - future <- structure(core, class = c("Future", class(core))) - future <- makeFutureJournal(future, start = t_start) - future + structure(core, class = c("Future", class(core))) } @@ -446,12 +444,40 @@ run.Future <- function(future, ...) { future } -run <- function(...) UseMethod("run") +#' @export +#' @keywords internal +run <- function(future, ...) { + ## Automatically update journal entries for Future object + if (inherits(future, "Future")) { + start <- Sys.time() + on.exit({ + appendToFutureJournal(future, + step = "launch", + start = start, + stop = Sys.time() + ) + }) + } + UseMethod("run") +} #' @export #' @keywords internal -result <- function(...) UseMethod("result") +result <- function(future, ...) { + ## Automatically update journal entries for Future object + if (inherits(future, "Future")) { + start <- Sys.time() + on.exit({ + appendToFutureJournal(future, + step = "gather", + start = start, + stop = Sys.time() + ) + }) + } + UseMethod("result") +} #' Get the results of a resolved future #' diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index 13cc4b58..b9f2061b 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -41,8 +41,6 @@ MulticoreFuture <- function(expr = NULL, substitute = TRUE, envir = parent.frame future <- as_MulticoreFuture(future, ...) - updateFutureJournal(future, "create") - future } diff --git a/R/future.R b/R/future.R index 1aeff3bd..69c43653 100644 --- a/R/future.R +++ b/R/future.R @@ -188,6 +188,7 @@ #' @name future future <- function(expr, envir = parent.frame(), substitute = TRUE, lazy = FALSE, seed = FALSE, globals = TRUE, packages = NULL, stdout = TRUE, conditions = "condition", earlySignal = FALSE, label = NULL, gc = FALSE, ...) { if (substitute) expr <- substitute(expr) + t_start <- Sys.time() gp <- getGlobalsAndPackages(expr, envir = envir, tweak = tweakExpression, globals = globals) expr <- gp$expr @@ -216,13 +217,15 @@ future <- function(expr, envir = parent.frame(), substitute = TRUE, lazy = FALSE ## Comment: Only allowed for persistent 'cluster' futures future$.defaultLocal <- !is.element("local", names(list(...))) + future <- makeFutureJournal(future, start = t_start) + if (!lazy) { future <- run(future) future$lazy <- FALSE ## Assert that a future was returned stop_if_not(inherits(future, "Future"), !future$lazy) } - + future } diff --git a/R/journal.R b/R/journal.R index 9e77cfa1..95e622dd 100644 --- a/R/journal.R +++ b/R/journal.R @@ -5,7 +5,7 @@ #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step`, `start`, `stop`, and `duration`.a +#' A data frame with columns `step`, `start`, `stop`, and `duration`. #' #' @export journal <- function(x, ...) UseMethod("journal") @@ -40,6 +40,7 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time()) { stop_if_not( inherits(x, "Future"), + is.null(x$.journal), length(step) == 1L, is.character(step), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") @@ -53,6 +54,9 @@ makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time( updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { + ## Nothing to do? + if (!inherits(x$.journal, "FutureJournal")) return(x) + stop_if_not( inherits(x, "Future"), length(step) == 1L, is.character(step), @@ -77,14 +81,19 @@ updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { } -appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct(NA_real_)) { +appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { + ## Nothing to do? + if (!inherits(x$.journal, "FutureJournal")) return(x) + + if (skip && is.element(step, x$.journal$step)) return(x) + stop_if_not( inherits(x, "Future"), length(step) == 1L, is.character(step), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - + data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) x$.journal <- rbind(x$.journal, data) invisible(x) diff --git a/R/resolved.R b/R/resolved.R index 5ecdb77c..c93bb3f5 100644 --- a/R/resolved.R +++ b/R/resolved.R @@ -19,7 +19,21 @@ #' e.g. `while (!resolved(future)) Sys.sleep(5)`. #' #' @export -resolved <- function(x, ...) UseMethod("resolved") +resolved <- function(x, ...) { + ## Automatically update journal entries for Future object + if (inherits(x, "Future")) { + start <- Sys.time() + on.exit({ + appendToFutureJournal(x, + step = "resolved", + start = start, + stop = Sys.time(), + skip = FALSE + ) + }) + } + UseMethod("resolved") +} #' @export resolved.default <- function(x, ...) TRUE diff --git a/man/journal.Rd b/man/journal.Rd index a28763f9..059aa29a 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,7 +12,7 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}.a +A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}. } \description{ Gets a journal of events for a future From 49ddd9a09632aa8f7aab3ccff14b87e394242e67 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 15:48:38 -0800 Subject: [PATCH 11/88] journal(): Sort by 'start' --- R/journal.R | 3 +++ 1 file changed, 3 insertions(+) diff --git a/R/journal.R b/R/journal.R index 95e622dd..eb1b2e38 100644 --- a/R/journal.R +++ b/R/journal.R @@ -26,6 +26,9 @@ journal.Future <- function(x, ...) { stop_if_not(inherits(data, "FutureJournal")) } + ## Sort by start time + if (nrow(data) > 1L) data <- data[order(data$start), ] + data } From 8dd9c721f425a368c260257417416613eccf71e7 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 25 Feb 2022 16:04:24 -0800 Subject: [PATCH 12/88] journal(): calculate relative start time (at) and duration on the fly --- R/journal.R | 19 ++++++++++++++----- man/journal.Rd | 7 ++++++- 2 files changed, 20 insertions(+), 6 deletions(-) diff --git a/R/journal.R b/R/journal.R index eb1b2e38..ce5f9c59 100644 --- a/R/journal.R +++ b/R/journal.R @@ -5,7 +5,12 @@ #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step`, `start`, `stop`, and `duration`. +#' A data frame with columns `step`, `start`, `stop`, `at`, and `duration`, +#' where the latter two are calculated from `start` and `stop`. +#' The data frame is sorted by the `start` time. +#' Note that the timestamps for the `evaluate` step are based on the local +#' time on the worker. The system clocks on the worker and the calling R +#' system may be out of sync. #' #' @export journal <- function(x, ...) UseMethod("journal") @@ -27,7 +32,12 @@ journal.Future <- function(x, ...) { } ## Sort by start time - if (nrow(data) > 1L) data <- data[order(data$start), ] + n <- nrow(data) + if (n > 1L) data <- data[order(data$start), ] + + ## Append 'at' and 'duration' + data$at <- data$start - data$start[1] + data$duration <- data$stop - data$start data } @@ -49,7 +59,7 @@ makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time( length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + data <- data.frame(step = step, start = start, stop = stop) class(data) <- c("FutureJournal", class(data)) x$.journal <- data invisible(x) @@ -76,7 +86,6 @@ updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { entry <- data[row, ] if (!is.null(start)) entry$start <- start if (!is.null(stop)) entry$stop <- stop - entry$duration <- entry$stop - entry$start data[row, ] <- entry stop_if_not(inherits(data, "FutureJournal")) x$.journal <- data @@ -97,7 +106,7 @@ appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(step = step, start = start, stop = stop, duration = stop - start) + data <- data.frame(step = step, start = start, stop = stop) x$.journal <- rbind(x$.journal, data) invisible(x) } diff --git a/man/journal.Rd b/man/journal.Rd index 059aa29a..aa304660 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,7 +12,12 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step}, \code{start}, \code{stop}, and \code{duration}. +A data frame with columns \code{step}, \code{start}, \code{stop}, \code{at}, and \code{duration}, +where the latter two are calculated from \code{start} and \code{stop}. +The data frame is sorted by the \code{start} time. +Note that the timestamps for the \code{evaluate} step are based on the local +time on the worker. The system clocks on the worker and the calling R +system may be out of sync. } \description{ Gets a journal of events for a future From 3c7ef32ae1d710801d7f680d00adeefab52d6856 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sat, 26 Feb 2022 21:01:58 -0800 Subject: [PATCH 13/88] Avoid exporting journal() for now; it'll be under heavy development for quite some time --- NAMESPACE | 1 - NEWS | 5 +++-- R/journal.R | 30 +++++++++++++++++++----------- incl/journal.R | 12 ++++++++++++ man/journal.Rd | 20 +++++++++++++++++--- 5 files changed, 51 insertions(+), 17 deletions(-) create mode 100644 incl/journal.R diff --git a/NAMESPACE b/NAMESPACE index 13fe3323..a0d709d8 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -119,7 +119,6 @@ export(futureSessionInfo) export(futures) export(getExpression) export(getGlobalsAndPackages) -export(journal) export(makeClusterMPI) export(makeClusterPSOCK) export(makeNodePSOCK) diff --git a/NEWS b/NEWS index 5f5703e7..d1a29ee6 100644 --- a/NEWS +++ b/NEWS @@ -16,8 +16,9 @@ PERFORMANCE: BETA FEATURES: - * Add journal() for retrieving timing information of internal events for - a specific future. + * Add internal journal() for retrieving timing information of internal + events for a specific future. This function is non-exported for now, + because it is under development. Please do _not_ use it in a package. Version: 1.24.0 [2022-02-19] diff --git a/R/journal.R b/R/journal.R index ce5f9c59..955b50ae 100644 --- a/R/journal.R +++ b/R/journal.R @@ -2,23 +2,30 @@ #' #' @param x A [Future] object. #' +## @param baseline (POSIXct; optional) A baseline timestamp that the +## relative start time (`at`) should be calculated towards. The default +## is the first `start` time in the journal. +#' #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step`, `start`, `stop`, `at`, and `duration`, -#' where the latter two are calculated from `start` and `stop`. -#' The data frame is sorted by the `start` time. +#' A data frame with columns `step` (character string), `start` (POSIXct), +#' `at` (difftime), and `duration` (difftime). +#' The data frame is sorted by the `at` time. #' Note that the timestamps for the `evaluate` step are based on the local #' time on the worker. The system clocks on the worker and the calling R #' system may be out of sync. #' -#' @export +#' @example incl/journal.R journal <- function(x, ...) UseMethod("journal") #' @export -journal.Future <- function(x, ...) { +journal.Future <- function(x, baseline = NULL, ...) { data <- x$.journal - stop_if_not(inherits(data, "FutureJournal")) + stop_if_not( + inherits(data, "FutureJournal"), + is.null(baseline) || (length(baseline) == 1L && inherits(baseline, "POSIXct")) + ) ## Backward compatibility (until all backends does this) if (!is.element("evaluate", data$step) && !is.null(x$result)) { @@ -31,13 +38,14 @@ journal.Future <- function(x, ...) { stop_if_not(inherits(data, "FutureJournal")) } - ## Sort by start time - n <- nrow(data) - if (n > 1L) data <- data[order(data$start), ] - ## Append 'at' and 'duration' - data$at <- data$start - data$start[1] + if (is.null(baseline)) baseline <- data$start[1] + data$at <- data$start - baseline data$duration <- data$stop - data$start + data$stop <- NULL + + ## Sort by relative start time + if (nrow(data) > 1L) data <- data[order(data$at), ] data } diff --git a/incl/journal.R b/incl/journal.R new file mode 100644 index 00000000..13ad71e0 --- /dev/null +++ b/incl/journal.R @@ -0,0 +1,12 @@ +library(future) +journal <- future:::journal +plan(multisession, workers = 2L) + +t_start <- Sys.time() +fs <- lapply(1:3, FUN = function(x) future({ Sys.sleep(x); sqrt(x) })) +vs <- value(fs) +js <- lapply(fs, FUN = journal, baseline = t_start) +print(js) + +## Stop parallel workers +plan(sequential) diff --git a/man/journal.Rd b/man/journal.Rd index aa304660..7e0274fd 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,9 +12,9 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step}, \code{start}, \code{stop}, \code{at}, and \code{duration}, -where the latter two are calculated from \code{start} and \code{stop}. -The data frame is sorted by the \code{start} time. +A data frame with columns \code{step} (character string), \code{start} (POSIXct), +\code{at} (difftime), and \code{duration} (difftime). +The data frame is sorted by the \code{at} time. Note that the timestamps for the \code{evaluate} step are based on the local time on the worker. The system clocks on the worker and the calling R system may be out of sync. @@ -22,3 +22,17 @@ system may be out of sync. \description{ Gets a journal of events for a future } +\examples{ +library(future) +journal <- future:::journal +plan(multisession, workers = 2L) + +t_start <- Sys.time() +fs <- lapply(1:3, FUN = function(x) future({ Sys.sleep(x); sqrt(x) })) +vs <- value(fs) +js <- lapply(fs, FUN = journal, baseline = t_start) +print(js) + +## Stop parallel workers +plan(sequential) +} From 856cdf3df65a67ddf26d7ea43b327a7d47d3eaaf Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sat, 26 Feb 2022 21:31:39 -0800 Subject: [PATCH 14/88] Now FutureResult objects hold the session UUID of the worker. journal() returns also the future label and the UUID. It also return the session UUID, which is either the calling session or the worker session (for the 'evaluation' step). --- R/FutureResult-class.R | 19 ++++++++++--------- R/journal.R | 25 +++++++++++++++++++++++-- 2 files changed, 33 insertions(+), 11 deletions(-) diff --git a/R/FutureResult-class.R b/R/FutureResult-class.R index ddd68980..16a143d7 100644 --- a/R/FutureResult-class.R +++ b/R/FutureResult-class.R @@ -71,16 +71,17 @@ FutureResult <- local({ } structure(list( - value = value, - visible = visible, - stdout = stdout, - conditions = conditions, - rng = rng, + value = value, + visible = visible, + stdout = stdout, + conditions = conditions, + rng = rng, ..., - started = started, - finished = finished, - r_info = r_info, - version = version + started = started, + finished = finished, + session_uuid = session_uuid(), + r_info = r_info, + version = version ), class = "FutureResult") } }) diff --git a/R/journal.R b/R/journal.R index 955b50ae..2b9ddc3c 100644 --- a/R/journal.R +++ b/R/journal.R @@ -9,8 +9,16 @@ #' @param \ldots Not used. #' #' @return -#' A data frame with columns `step` (character string), `start` (POSIXct), -#' `at` (difftime), and `duration` (difftime). +#' A data frame with columns: +#' +#' 1. `step` (character string) +#' 2. `start` (POSIXct) +#' 3. `at` (difftime) +#' 4. `duration` (difftime) +#' 5. `future_label` (character string) +#' 6. `future_uuid` (character string) +#' 7. `session_uuid` (character string) +#' #' The data frame is sorted by the `at` time. #' Note that the timestamps for the `evaluate` step are based on the local #' time on the worker. The system clocks on the worker and the calling R @@ -26,15 +34,19 @@ journal.Future <- function(x, baseline = NULL, ...) { inherits(data, "FutureJournal"), is.null(baseline) || (length(baseline) == 1L && inherits(baseline, "POSIXct")) ) + + session_uuid <- rep(x$owner, times = nrow(data)) ## Backward compatibility (until all backends does this) if (!is.element("evaluate", data$step) && !is.null(x$result)) { + stop_if_not(is.character(session_uuid)) x <- appendToFutureJournal(x, step = "evaluate", start = x$result$started, stop = x$result$finished ) data <- x$.journal + session_uuid <- c(session_uuid, x$result$session_uuid) stop_if_not(inherits(data, "FutureJournal")) } @@ -44,6 +56,15 @@ journal.Future <- function(x, baseline = NULL, ...) { data$duration <- data$stop - data$start data$stop <- NULL + ## Append future 'label' + data$future_label <- if (is.null(x$label)) NA_character_ else x$label + + ## Append future UUID + data$future_uuid <- x$uuid + + ## Append session UUID + data$session_uuid <- session_uuid + ## Sort by relative start time if (nrow(data) > 1L) data <- data[order(data$at), ] From 927b3a24fba52537c07d41464787797ce585dcfb Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 28 Feb 2022 15:49:31 -0800 Subject: [PATCH 15/88] Add journal() for lists (of Future:s or FutureJournal:s) and for FutureJournal (to change 'baseline') --- NAMESPACE | 2 ++ R/journal.R | 22 ++++++++++++++++++++++ man/journal.Rd | 13 +++++++++++-- 3 files changed, 35 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index a0d709d8..8ae3f9ec 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -17,6 +17,8 @@ S3method(getExpression,MulticoreFuture) S3method(getExpression,MultisessionFuture) S3method(getExpression,UniprocessFuture) S3method(journal,Future) +S3method(journal,FutureJournal) +S3method(journal,list) S3method(mandelbrot,matrix) S3method(mandelbrot,numeric) S3method(nbrOfFreeWorkers,"NULL") diff --git a/R/journal.R b/R/journal.R index 2b9ddc3c..07558336 100644 --- a/R/journal.R +++ b/R/journal.R @@ -71,6 +71,28 @@ journal.Future <- function(x, baseline = NULL, ...) { data } +#' @export +journal.FutureJournal <- function(x, baseline = NULL, ...) { + if (!is.null(baseline)) { + x$at <- x$at - baseline + } + x +} + +#' @export +journal.list <- function(x, index = seq_along(x), ...) { + if (!is.null(index)) { + stop_if_not(length(index) == length(x)) + x <- lapply(index, FUN = function(idx) { + journal <- journal(x[[idx]], ...) + stop_if_not(inherits(journal, "FutureJournal")) + cbind(index = idx, journal) + }) + } + Reduce(rbind, x) +} + + #' @export print.FutureJournal <- function(x, digits.secs = 3L, ...) { oopts <- options(digits.secs = digits.secs) diff --git a/man/journal.Rd b/man/journal.Rd index 7e0274fd..a73ccf0f 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,8 +12,17 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns \code{step} (character string), \code{start} (POSIXct), -\code{at} (difftime), and \code{duration} (difftime). +A data frame with columns: +\enumerate{ +\item \code{step} (character string) +\item \code{start} (POSIXct) +\item \code{at} (difftime) +\item \code{duration} (difftime) +\item \code{future_label} (character string) +\item \code{future_uuid} (character string) +\item \code{session_uuid} (character string) +} + The data frame is sorted by the \code{at} time. Note that the timestamps for the \code{evaluate} step are based on the local time on the worker. The system clocks on the worker and the calling R From 7d4fd1fcfc5c09a7aa5917d1d609daa6a7d28d43 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 28 Feb 2022 18:20:24 -0800 Subject: [PATCH 16/88] journal(..., baseline = TRUE) for futures/journals now sets the zero-time relative start time to the minimal observed timestamp --- R/journal.R | 44 ++++++++++++++++++++++++++++---------------- 1 file changed, 28 insertions(+), 16 deletions(-) diff --git a/R/journal.R b/R/journal.R index 07558336..24ccc3e4 100644 --- a/R/journal.R +++ b/R/journal.R @@ -2,9 +2,9 @@ #' #' @param x A [Future] object. #' -## @param baseline (POSIXct; optional) A baseline timestamp that the -## relative start time (`at`) should be calculated towards. The default -## is the first `start` time in the journal. +## @param baseline (POSIXct; optional) A timestamp to server as time zero +## for the relative start time (`at`). If `TRUE` (default), then the +## earliest timepoint observed is used as the baseline. #' #' @param \ldots Not used. #' @@ -28,12 +28,9 @@ journal <- function(x, ...) UseMethod("journal") #' @export -journal.Future <- function(x, baseline = NULL, ...) { +journal.Future <- function(x, ...) { data <- x$.journal - stop_if_not( - inherits(data, "FutureJournal"), - is.null(baseline) || (length(baseline) == 1L && inherits(baseline, "POSIXct")) - ) + stop_if_not(inherits(data, "FutureJournal")) session_uuid <- rep(x$owner, times = nrow(data)) @@ -50,8 +47,10 @@ journal.Future <- function(x, baseline = NULL, ...) { stop_if_not(inherits(data, "FutureJournal")) } + ## Find relative time zero + baseline <- min(data$start, na.rm = TRUE) + ## Append 'at' and 'duration' - if (is.null(baseline)) baseline <- data$start[1] data$at <- data$start - baseline data$duration <- data$stop - data$start data$stop <- NULL @@ -73,23 +72,36 @@ journal.Future <- function(x, baseline = NULL, ...) { #' @export journal.FutureJournal <- function(x, baseline = NULL, ...) { + ## Reset relative time zero? if (!is.null(baseline)) { - x$at <- x$at - baseline + if (isTRUE(baseline)) baseline <- min(x$start, na.rm = TRUE) + x$at <- x$start - baseline } x } #' @export -journal.list <- function(x, index = seq_along(x), ...) { +journal.list <- function(x, index = seq_along(x), baseline = TRUE, ...) { + ## Reset relative time zero to the first observed timestamp? + if (isTRUE(baseline)) { + stop_if_not(baseline >= 1L, baseline <= length(x)) + x <- lapply(x, FUN = journal, ...) + start <- lapply(x, FUN = function(x) min(x$start, na.rm = TRUE)) + start <- Reduce(c, start) + baseline <- min(start, na.rm = TRUE) + } + + js <- lapply(x, FUN = journal, baseline = baseline, ...) + + ## Add index? if (!is.null(index)) { stop_if_not(length(index) == length(x)) - x <- lapply(index, FUN = function(idx) { - journal <- journal(x[[idx]], ...) - stop_if_not(inherits(journal, "FutureJournal")) - cbind(index = idx, journal) + js <- lapply(index, FUN = function(idx) { + cbind(index = idx, js[[idx]]) }) } - Reduce(rbind, x) + + Reduce(rbind, js) } From 99c1ea5513e874582dc9789a1f112a870242813c Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 28 Feb 2022 20:21:35 -0800 Subject: [PATCH 17/88] Journal: record also resolve() --- R/resolve.R | 15 ++++++++++++++- 1 file changed, 14 insertions(+), 1 deletion(-) diff --git a/R/resolve.R b/R/resolve.R index ad9248aa..a7328586 100644 --- a/R/resolve.R +++ b/R/resolve.R @@ -44,7 +44,9 @@ #' `resolve(futureOf(x))`. #' #' @export -resolve <- function(x, idxs = NULL, recursive = 0, result = FALSE, stdout = FALSE, signal = FALSE, force = FALSE, sleep = 1.0, value = result, ...) UseMethod("resolve") +resolve <- function(x, idxs = NULL, recursive = 0, result = FALSE, stdout = FALSE, signal = FALSE, force = FALSE, sleep = 1.0, value = result, ...) { + UseMethod("resolve") +} #' @export resolve.default <- function(x, ...) x @@ -56,6 +58,17 @@ resolve.Future <- function(x, idxs = NULL, recursive = 0, result = FALSE, stdout .Defunct(msg = "Argument 'value' of resolve() is defunct. It was deprecated in future (>= 1.15.0). Use 'result' instead.", package = .packageName) } + ## Automatically update journal entries for Future object + t_start <- Sys.time() + on.exit({ + appendToFutureJournal(x, + step = "resolve", + start = t_start, + stop = Sys.time(), + skip = FALSE + ) + }) + if (is.logical(recursive)) { if (recursive) recursive <- getOption("future.resolve.recursive", 99) } From 35849a8e50200cb78da6ef905216580ee71d39b5 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 28 Feb 2022 20:22:18 -0800 Subject: [PATCH 18/88] journal: record requesting a free worker, worker cleanup, package attaching, and exporting of globals --- R/ClusterFuture-class.R | 27 +++++++++++++++++++++++++-- R/MulticoreFuture-class.R | 9 +++++++++ 2 files changed, 34 insertions(+), 2 deletions(-) diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index b2a66975..88f952d1 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -119,8 +119,8 @@ run.ClusterFuture <- function(future, ...) { ## FutureRegistry to use reg <- sprintf("workers-%s", attr(workers, "name", exact = TRUE)) - ## Next available cluster node + t_start <- Sys.time() node_idx <- requestNode(await = function() { FutureRegistry(reg, action = "collect-first", earlySignal = TRUE) }, workers = workers) @@ -128,6 +128,12 @@ run.ClusterFuture <- function(future, ...) { ## Cluster node to use cl <- workers[node_idx] + + appendToFutureJournal(future, + step = "getWorker", + start = t_start, + stop = Sys.time() + ) ## (i) Reset global environment of cluster node such that @@ -135,7 +141,13 @@ run.ClusterFuture <- function(future, ...) { ## may happen even if the future is evaluated inside a ## local, e.g. local({ a <<- 1 }). if (!persistent) { + t_start <- Sys.time() cluster_call(cl, fun = grmall, future = future, when = "call grmall() on") + appendToFutureJournal(future, + step = "eraseWorker", + start = t_start, + stop = Sys.time() + ) } @@ -143,6 +155,7 @@ run.ClusterFuture <- function(future, ...) { ## NOTE: Already take care of by getExpression() of the Future class. ## However, if we need to get an early error about missing packages, ## we can get the error here before launching the future. + t_start <- Sys.time() packages <- packages(future) if (future$earlySignal && length(packages) > 0) { if (debug) mdebugf("Attaching %d packages (%s) on cluster node #%d ...", @@ -153,11 +166,16 @@ run.ClusterFuture <- function(future, ...) { if (debug) mdebugf("Attaching %d packages (%s) on cluster node #%d ... DONE", length(packages), hpaste(sQuote(packages)), node_idx) } - + appendToFutureJournal(future, + step = "attachPackages", + start = t_start, + stop = Sys.time() + ) ## (iii) Export globals globals <- globals(future) if (length(globals) > 0) { + t_start <- Sys.time() if (debug) { total_size <- asIEC(objectSize(globals)) mdebugf("Exporting %d global objects (%s) to cluster node #%d ...", length(globals), total_size, node_idx) @@ -180,6 +198,11 @@ run.ClusterFuture <- function(future, ...) { value <- NULL } if (debug) mdebugf("Exporting %d global objects (%s) to cluster node #%d ... DONE", length(globals), total_size, node_idx) + appendToFutureJournal(future, + step = "exportGlobals", + start = t_start, + stop = Sys.time() + ) } ## Not needed anymore globals <- NULL diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index b9f2061b..d8e80a9d 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -73,12 +73,21 @@ run.MulticoreFuture <- function(future, ...) { expr <- getExpression(future) envir <- future$envir + ## Get a free worker + t_start <- Sys.time() + reg <- sprintf("multicore-%s", session_uuid()) requestCore( await = function() FutureRegistry(reg, action = "collect-first", earlySignal = TRUE), workers = future$workers ) + appendToFutureJournal(future, + step = "getWorker", + start = t_start, + stop = Sys.time() + ) + ## Add to registry FutureRegistry(reg, action = "add", future = future, earlySignal = TRUE) From 6a6ca55838d99a58b9a81f83b5bc3b291df97f94 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 1 Mar 2022 14:12:22 -0800 Subject: [PATCH 19/88] Add FutureJournalCondition and signalling of it at the end of result() --- NAMESPACE | 2 ++ R/Future-class.R | 11 ++++++++++- R/journal.R | 18 ++++++++++++++++++ man/FutureCondition.Rd | 11 ++++++++++- tests/tweak.R | 2 ++ 5 files changed, 42 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 8ae3f9ec..c15e78b7 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -18,6 +18,7 @@ S3method(getExpression,MultisessionFuture) S3method(getExpression,UniprocessFuture) S3method(journal,Future) S3method(journal,FutureJournal) +S3method(journal,FutureJournalCondition) S3method(journal,list) S3method(mandelbrot,matrix) S3method(mandelbrot,numeric) @@ -93,6 +94,7 @@ export(Future) export(FutureCondition) export(FutureError) export(FutureGlobals) +export(FutureJournalCondition) export(FutureMessage) export(FutureResult) export(FutureWarning) diff --git a/R/Future-class.R b/R/Future-class.R index 43725602..3d487042 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -466,7 +466,8 @@ run <- function(future, ...) { #' @keywords internal result <- function(future, ...) { ## Automatically update journal entries for Future object - if (inherits(future, "Future")) { + if (inherits(future, "Future") && + inherits(future$.journal, "FutureJournal")) { start <- Sys.time() on.exit({ appendToFutureJournal(future, @@ -474,6 +475,14 @@ result <- function(future, ...) { start = start, stop = Sys.time() ) + + ## Signal FutureJournalCondition + journal <- journal(future) + label <- future$label + if (is.null(label)) label <- "" + msg <- sprintf("A future ('%s') of class %s was resolved", label, class(future)[1]) + cond <- FutureJournalCondition(message = msg, journal = journal) + signalCondition(cond) }) } UseMethod("result") diff --git a/R/journal.R b/R/journal.R index 24ccc3e4..4d4b9b5e 100644 --- a/R/journal.R +++ b/R/journal.R @@ -173,3 +173,21 @@ appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct x$.journal <- rbind(x$.journal, data) invisible(x) } + + + +#' @rdname FutureCondition +#' @export +FutureJournalCondition <- function(message, journal, call = NULL, uuid = future$uuid, future = NULL) { + stop_if_not(inherits(journal, "FutureJournal")) + cond <- FutureCondition(message = message, call = call, uuid = uuid, future = future) + cond$journal <- journal + class <- c("FutureJournalCondition", class(cond)) + class(cond) <- class[!duplicated(class, fromLast = TRUE)] + cond +} + +#' @export +journal.FutureJournalCondition <- function(x, ...) { + x$journal +} diff --git a/man/FutureCondition.Rd b/man/FutureCondition.Rd index 58b9b8ce..3980656a 100644 --- a/man/FutureCondition.Rd +++ b/man/FutureCondition.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/FutureCondition-class.R +% Please edit documentation in R/FutureCondition-class.R, R/journal.R \name{FutureCondition} \alias{FutureCondition} \alias{FutureMessage} @@ -9,6 +9,7 @@ \alias{RngFutureWarning} \alias{RngFutureError} \alias{UnexpectedFutureResultError} +\alias{FutureJournalCondition} \title{A condition (message, warning, or error) that occurred while orchestrating a future} \usage{ FutureCondition(message, call = NULL, uuid = future$uuid, future = NULL) @@ -31,6 +32,14 @@ RngFutureWarning(...) RngFutureError(...) UnexpectedFutureResultError(future, hint = NULL) + +FutureJournalCondition( + message, + journal, + call = NULL, + uuid = future$uuid, + future = NULL +) } \arguments{ \item{message}{A message condition.} diff --git a/tests/tweak.R b/tests/tweak.R index ea357f8e..454313d3 100644 --- a/tests/tweak.R +++ b/tests/tweak.R @@ -41,6 +41,7 @@ stopifnot(!identical(sequential2, future::sequential)) stopifnot(inherits(sequential2, "tweaked")) stopifnot(identical(formals(sequential2)$abc, FALSE)) + message("*** y <- tweak('sequential', abc = FALSE, abc = 1, def = TRUE) ...") res <- tryCatch({ sequential2 <- future::tweak('sequential', abc = FALSE, abc = 1, def = TRUE) @@ -55,6 +56,7 @@ stopifnot(inherits(sequential2, "tweaked")) stopifnot(identical(formals(sequential2)$abc, FALSE)) + message("*** y <- tweak(cluster, rscript_startup = quote(...)) ...") cl <- 42L cluster2 <- tweak(cluster, workers = cl, rscript_startup = quote(options(abc = 42L))) From e2bc8e83e1f8b9946f1cc2e473d78feef01f8e21 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 1 Mar 2022 14:35:52 -0800 Subject: [PATCH 20/88] journal: more sanity checks --- R/journal.R | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/R/journal.R b/R/journal.R index 4d4b9b5e..6991b9c6 100644 --- a/R/journal.R +++ b/R/journal.R @@ -31,8 +31,10 @@ journal <- function(x, ...) UseMethod("journal") journal.Future <- function(x, ...) { data <- x$.journal stop_if_not(inherits(data, "FutureJournal")) - - session_uuid <- rep(x$owner, times = nrow(data)) + session_uuid <- x$owner + stop_if_not(length(session_uuid) == 1L, is.character(session_uuid), !is.na(session_uuid)) + + session_uuid <- rep(session_uuid, times = nrow(data)) ## Backward compatibility (until all backends does this) if (!is.element("evaluate", data$step) && !is.null(x$result)) { @@ -43,6 +45,7 @@ journal.Future <- function(x, ...) { stop = x$result$finished ) data <- x$.journal + stop_if_not(length(x$result$session_uuid) == 1L, is.character(x$result$session_uuid)) session_uuid <- c(session_uuid, x$result$session_uuid) stop_if_not(inherits(data, "FutureJournal")) } From f842a6ade45181628643f665272a41f27dab9589 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 1 Mar 2022 14:57:51 -0800 Subject: [PATCH 21/88] For now, journaling has to be enabled by options(future.journal = TRUE) --- R/future.R | 5 ++++- R/journal.R | 5 +++++ incl/journal.R | 7 ++++++- man/journal.Rd | 7 ++++++- 4 files changed, 21 insertions(+), 3 deletions(-) diff --git a/R/future.R b/R/future.R index 69c43653..e4e8ded9 100644 --- a/R/future.R +++ b/R/future.R @@ -217,7 +217,10 @@ future <- function(expr, envir = parent.frame(), substitute = TRUE, lazy = FALSE ## Comment: Only allowed for persistent 'cluster' futures future$.defaultLocal <- !is.element("local", names(list(...))) - future <- makeFutureJournal(future, start = t_start) + ## Enable journaling? + if (getOption("future.journal", FALSE)) { + future <- makeFutureJournal(future, start = t_start) + } if (!lazy) { future <- run(future) diff --git a/R/journal.R b/R/journal.R index 6991b9c6..f8624c8f 100644 --- a/R/journal.R +++ b/R/journal.R @@ -30,6 +30,11 @@ journal <- function(x, ...) UseMethod("journal") #' @export journal.Future <- function(x, ...) { data <- x$.journal + if (is.null(data)) { + label <- x$label + if (is.null(label)) label <- "" + stop(sprintf("No journal is available for future ('%s'). Did you forget to enable journaling?", label)) + } stop_if_not(inherits(data, "FutureJournal")) session_uuid <- x$owner stop_if_not(length(session_uuid) == 1L, is.character(session_uuid), !is.na(session_uuid)) diff --git a/incl/journal.R b/incl/journal.R index 13ad71e0..0670e7c1 100644 --- a/incl/journal.R +++ b/incl/journal.R @@ -1,5 +1,9 @@ library(future) journal <- future:::journal + +## Enable journaling of futures +oopts <- options(future.journal = TRUE) + plan(multisession, workers = 2L) t_start <- Sys.time() @@ -8,5 +12,6 @@ vs <- value(fs) js <- lapply(fs, FUN = journal, baseline = t_start) print(js) -## Stop parallel workers +## Stop parallel workers and undo journaling settings plan(sequential) +options(oopts) diff --git a/man/journal.Rd b/man/journal.Rd index a73ccf0f..8cb8e703 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -34,6 +34,10 @@ Gets a journal of events for a future \examples{ library(future) journal <- future:::journal + +## Enable journaling of futures +oopts <- options(future.journal = TRUE) + plan(multisession, workers = 2L) t_start <- Sys.time() @@ -42,6 +46,7 @@ vs <- value(fs) js <- lapply(fs, FUN = journal, baseline = t_start) print(js) -## Stop parallel workers +## Stop parallel workers and undo journaling settings plan(sequential) +options(oopts) } From f9481ff2e67057060469e1fd031ff3b760cd4d1d Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 1 Mar 2022 20:17:12 -0800 Subject: [PATCH 22/88] update WORDLIST --- inst/WORDLIST | 2 ++ 1 file changed, 2 insertions(+) diff --git a/inst/WORDLIST b/inst/WORDLIST index a3565a5f..abab870e 100644 --- a/inst/WORDLIST +++ b/inst/WORDLIST @@ -455,3 +455,5 @@ stan stanfit calc conditionMessage +difftime +POSIXct From 8c50378dd388c34e5c5683cb8c1de11bcd93ff09 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 2 Mar 2022 09:35:18 -0800 Subject: [PATCH 23/88] result(): Signal FutureJournalCondition only once --- R/Future-class.R | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/R/Future-class.R b/R/Future-class.R index 3d487042..87a1ce44 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -476,13 +476,16 @@ result <- function(future, ...) { stop = Sys.time() ) - ## Signal FutureJournalCondition - journal <- journal(future) - label <- future$label - if (is.null(label)) label <- "" - msg <- sprintf("A future ('%s') of class %s was resolved", label, class(future)[1]) - cond <- FutureJournalCondition(message = msg, journal = journal) - signalCondition(cond) + ## Signal FutureJournalCondition? + if (!isTRUE(future$.journal_signalled)) { + journal <- journal(future) + label <- future$label + if (is.null(label)) label <- "" + msg <- sprintf("A future ('%s') of class %s was resolved", label, class(future)[1]) + cond <- FutureJournalCondition(message = msg, journal = journal) + signalCondition(cond) + future$.journal_signalled <- TRUE + } }) } UseMethod("result") From 8e03658a6f79d956271104830938880536033bfc Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 3 Mar 2022 14:46:21 -0800 Subject: [PATCH 24/88] journal(): Use factors for more fields --- R/journal.R | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/R/journal.R b/R/journal.R index f8624c8f..6385aa86 100644 --- a/R/journal.R +++ b/R/journal.R @@ -67,10 +67,17 @@ journal.Future <- function(x, ...) { data$future_label <- if (is.null(x$label)) NA_character_ else x$label ## Append future UUID - data$future_uuid <- x$uuid + data$future_uuid <- as.factor(x$uuid) ## Append session UUID - data$session_uuid <- session_uuid + data$session_uuid <- as.factor(session_uuid) + + ## Coerce 'step' to a factor + known_levels <- c("lifespan", "create", "launch", "resolved", "gather", "evaluate") + extra_levels <- c("attachPackages", "eraseWorker", "exportGlobals", "getWorker") + other_levels <- sort(setdiff(data$step, known_levels)) + levels <- c(known_levels, other_levels) + data$step <- factor(data$step, levels = levels) ## Sort by relative start time if (nrow(data) > 1L) data <- data[order(data$at), ] From 77f1c956f9b9f4556e6408c8504bdf3c21a032e6 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 1 May 2022 19:27:44 -0700 Subject: [PATCH 25/88] CLEANUP: split up enter-exit expression templates further --- DESCRIPTION | 2 +- NEWS | 2 +- R/expressions.R | 89 ++++++++++++++++++++++++++++--------------------- 3 files changed, 53 insertions(+), 40 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index e0601769..c7aac2c2 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.25.0-9908 +Version: 1.25.0-9909 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NEWS b/NEWS index d588fce4..45a53ad6 100644 --- a/NEWS +++ b/NEWS @@ -1,7 +1,7 @@ Package: future =============== -Version: 1.25.0-9908 [2022-04-30] +Version: 1.25.0-9909 [2022-05-01] SIGNIFICANT CHANGES: diff --git a/R/expressions.R b/R/expressions.R index edec1569..a0aa77a7 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -3,7 +3,7 @@ makeExpression <- local({ tmpl_expr_local <- bquote_compile(base::local(.(expr))) - tmpl_enter <- bquote_compile({ + tmpl_enter_optenvar <- bquote_compile({ ## Start time for future evaluation ...future.startTime <- base::Sys.time() @@ -16,36 +16,9 @@ makeExpression <- local({ ## https://github.com/Rdatatable/data.table/issues/5375 ...future.oldOptions <- base::as.list(base::.Options) ...future.oldEnvVars <- base::Sys.getenv() - - ## covr: skip=7 - base::options( - ## Prevent .future.R from being source():d when future is attached - future.startup.script = FALSE, - - ## Assert globals when future is created (or at run time)? - future.globals.onMissing = .(globals.onMissing), - - ## Pass down other future.* options - future.globals.maxSize = .(getOption("future.globals.maxSize")), - future.globals.method = .(getOption("future.globals.method")), - future.globals.onMissing = .(getOption("future.globals.onMissing")), - future.globals.onReference = .(getOption("future.globals.onReference")), - future.globals.resolve = .(getOption("future.globals.resolve")), - future.resolve.recursive = .(getOption("future.resolve.recursive")), - future.rng.onMisuse = .(getOption("future.rng.onMisuse")), - future.rng.onMisuse.keepFuture = .(getOption("future.rng.onMisuse.keepFuture")), - future.stdout.windows.reencode = .(getOption("future.stdout.windows.reencode")), - - ## Other options relevant to making futures behave consistently - ## across backends - width = .(getOption("width")) - ) - - ## Record above future options - ...future.futureOptionsAdded <- base::setdiff(base::names(base::.Options), base::names(...future.oldOptions)) }) - tmpl_exit <- bquote_compile({ + tmpl_exit_optenvar <- bquote_compile({ ## (a) Reset options base::options(...future.oldOptions) @@ -69,13 +42,6 @@ makeExpression <- local({ ## base::options(opts) ## } - ## (c) Remove any "future" options added - if (base::length(...future.futureOptionsAdded) > 0L) { - opts <- base::vector("list", length = base::length(...future.futureOptionsAdded)) - base::names(opts) <- ...future.futureOptionsAdded - base::options(opts) - } - ## (d) Reset environment variables if (.Platform$OS.type == "windows") { ## On MS Windows, you cannot have empty environment variables. When one @@ -116,6 +82,51 @@ makeExpression <- local({ .(exit) }) + + tmpl_enter_future_opts <- bquote_compile({ + .(enter) + + ## covr: skip=7 + base::options( + ## Prevent .future.R from being source():d when future is attached + future.startup.script = FALSE, + + ## Assert globals when future is created (or at run time)? + future.globals.onMissing = .(globals.onMissing), + + ## Pass down other future.* options + future.globals.maxSize = .(getOption("future.globals.maxSize")), + future.globals.method = .(getOption("future.globals.method")), + future.globals.onMissing = .(getOption("future.globals.onMissing")), + future.globals.onReference = .(getOption("future.globals.onReference")), + future.globals.resolve = .(getOption("future.globals.resolve")), + future.resolve.recursive = .(getOption("future.resolve.recursive")), + future.rng.onMisuse = .(getOption("future.rng.onMisuse")), + future.rng.onMisuse.keepFuture = .(getOption("future.rng.onMisuse.keepFuture")), + future.stdout.windows.reencode = .(getOption("future.stdout.windows.reencode")), + + ## Other options relevant to making futures behave consistently + ## across backends + width = .(getOption("width")) + ) + + ## Record above future options + ...future.futureOptionsAdded <- base::setdiff(base::names(base::.Options), base::names(...future.oldOptions)) + }) + + + tmpl_exit_future_opts <- bquote_compile({ + ## Remove any "future" options added + if (base::length(...future.futureOptionsAdded) > 0L) { + opts <- base::vector("list", length = base::length(...future.futureOptionsAdded)) + base::names(opts) <- ...future.futureOptionsAdded + base::options(opts) + } + + .(exit) + }) + + tmpl_expr_evaluate <- bquote_compile({ ## covr: skip=6 .(enter) @@ -297,8 +308,10 @@ makeExpression <- local({ } ## Set and reset certain future.* options etc. - enter <- bquote_apply(tmpl_enter) - exit <- bquote_apply(tmpl_exit) + enter <- bquote_apply(tmpl_enter_optenvar) + enter <- bquote_apply(tmpl_enter_future_opts) + exit <- bquote_apply(tmpl_exit_future_opts) + exit <- bquote_apply(tmpl_exit_optenvar) if (version == "1.8") { expr <- bquote_apply(tmpl_expr_evaluate) From 98fdbd95bdb93e313c8b92e918ca21742d45732f Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 1 May 2022 19:34:52 -0700 Subject: [PATCH 26/88] CLEANUP: make enter-exit expression templates symmetric --- DESCRIPTION | 2 +- NEWS | 2 +- R/Future-class.R | 4 ++-- R/UniprocessFuture-class.R | 2 +- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index c7aac2c2..c23f8bea 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.25.0-9909 +Version: 1.25.0-9910 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NEWS b/NEWS index 45a53ad6..6730855a 100644 --- a/NEWS +++ b/NEWS @@ -1,7 +1,7 @@ Package: future =============== -Version: 1.25.0-9909 [2022-05-01] +Version: 1.25.0-9910 [2022-05-01] SIGNIFICANT CHANGES: diff --git a/R/Future-class.R b/R/Future-class.R index 44e4935b..3828cb39 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -701,8 +701,8 @@ getExpression.Future <- local({ tmpl_exit_mccores <- bquote_compile({ ## covr: skip=2 - .(exit) base::options(mc.cores = ...future.mc.cores.old) + .(exit) }) tmpl_enter_rng <- bquote_compile({ @@ -744,7 +744,6 @@ getExpression.Future <- local({ ## Reset future strategies when done tmpl_exit_plan <- bquote_compile({ ## covr: skip=2 - .(exit) ## Reset option 'future.plan' and env var 'R_FUTURE_PLAN' options(future.plan = .(getOption("future.plan"))) if (is.na(.(oenv <- Sys.getenv("R_FUTURE_PLAN", NA_character_)))) @@ -752,6 +751,7 @@ getExpression.Future <- local({ else Sys.setenv(R_FUTURE_PLAN = .(oenv)) future::plan(.(strategies), .cleanup = FALSE, .init = FALSE) + .(exit) }) function(future, expr = future$expr, local = future$local, stdout = future$stdout, conditionClasses = future$conditions, split = future$split, mc.cores = NULL, exit = NULL, ...) { diff --git a/R/UniprocessFuture-class.R b/R/UniprocessFuture-class.R index 7c692cb9..e6565397 100644 --- a/R/UniprocessFuture-class.R +++ b/R/UniprocessFuture-class.R @@ -136,8 +136,8 @@ getExpression.UniprocessFuture <- local({ }) tmpl_exit_rng_undo <- bquote_compile({ - .(exit) base::assign(".Random.seed", .(oseed), envir = base::globalenv(), inherits = FALSE) + .(exit) }) function(future, immediateConditions = TRUE, exit = NULL, ...) { From 11fd404e4e892a699012fd606d5c80d57b148eb8 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 1 May 2022 19:44:38 -0700 Subject: [PATCH 27/88] Undo any changes to the current working directory during future evaluation (fix #611) --- DESCRIPTION | 2 +- NEWS | 6 +++++- R/expressions.R | 16 +++++++++++++++- 3 files changed, 21 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index c23f8bea..64f0c2a4 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.25.0-9910 +Version: 1.25.0-9911 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NEWS b/NEWS index 6730855a..56431961 100644 --- a/NEWS +++ b/NEWS @@ -1,7 +1,7 @@ Package: future =============== -Version: 1.25.0-9910 [2022-05-01] +Version: 1.25.0-9911 [2022-05-01] SIGNIFICANT CHANGES: @@ -15,6 +15,10 @@ SIGNIFICANT CHANGES: been added from loading a package and that are essential for that package to work. + * If it was changed while evaluating the future expression, the + current working directory is now reset when the future has been + resolved. + BUG FIXES: * Use of data.table in cluster and multisession futures broke in diff --git a/R/expressions.R b/R/expressions.R index a0aa77a7..3688a5b6 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -127,6 +127,17 @@ makeExpression <- local({ }) + tmpl_enter_workdir <- bquote_compile({ + .(enter) + ...future.workdir <- getwd() + }) + + tmpl_exit_workdir <- bquote_compile({ + if (!identical(...future.workdir, getwd())) setwd(...future.workdir) + .(exit) + }) + + tmpl_expr_evaluate <- bquote_compile({ ## covr: skip=6 .(enter) @@ -307,11 +318,14 @@ makeExpression <- local({ skip <- skip.local } - ## Set and reset certain future.* options etc. + ## Set and reset certain properties and states + enter <- bquote_apply(tmpl_enter_workdir) enter <- bquote_apply(tmpl_enter_optenvar) enter <- bquote_apply(tmpl_enter_future_opts) + exit <- bquote_apply(tmpl_exit_future_opts) exit <- bquote_apply(tmpl_exit_optenvar) + exit <- bquote_apply(tmpl_exit_workdir) if (version == "1.8") { expr <- bquote_apply(tmpl_expr_evaluate) From 05112faff0c24446f102a9ba94bb07ee5d9640b2 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 3 Jun 2022 17:52:46 -0700 Subject: [PATCH 28/88] Rename journal field 'step' to 'event' --- DESCRIPTION | 2 +- R/ClusterFuture-class.R | 8 +++--- R/Future-class.R | 4 +-- R/MulticoreFuture-class.R | 2 +- R/journal.R | 57 ++++++++++++++++++++++++--------------- R/resolve.R | 2 +- R/resolved.R | 2 +- man/journal.Rd | 15 ++++++++--- 8 files changed, 58 insertions(+), 34 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 83a2b59a..a3b0091a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9102 +Version: 1.26.1-9103 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 16d1a8f6..61594329 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -129,7 +129,7 @@ run.ClusterFuture <- function(future, ...) { cl <- workers[node_idx] appendToFutureJournal(future, - step = "getWorker", + event = "getWorker", start = t_start, stop = Sys.time() ) @@ -143,7 +143,7 @@ run.ClusterFuture <- function(future, ...) { t_start <- Sys.time() cluster_call(cl, fun = grmall, future = future, when = "call grmall() on") appendToFutureJournal(future, - step = "eraseWorker", + event = "eraseWorker", start = t_start, stop = Sys.time() ) @@ -166,7 +166,7 @@ run.ClusterFuture <- function(future, ...) { length(packages), hpaste(sQuote(packages)), node_idx) } appendToFutureJournal(future, - step = "attachPackages", + event = "attachPackages", start = t_start, stop = Sys.time() ) @@ -198,7 +198,7 @@ run.ClusterFuture <- function(future, ...) { } if (debug) mdebugf("Exporting %d global objects (%s) to cluster node #%d ... DONE", length(globals), total_size, node_idx) appendToFutureJournal(future, - step = "exportGlobals", + event = "exportGlobals", start = t_start, stop = Sys.time() ) diff --git a/R/Future-class.R b/R/Future-class.R index 44443c4b..c4715d3f 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -470,7 +470,7 @@ run <- function(future, ...) { start <- Sys.time() on.exit({ appendToFutureJournal(future, - step = "launch", + event = "launch", start = start, stop = Sys.time() ) @@ -489,7 +489,7 @@ result <- function(future, ...) { start <- Sys.time() on.exit({ appendToFutureJournal(future, - step = "gather", + event = "gather", start = start, stop = Sys.time() ) diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index 73219e19..53148c03 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -83,7 +83,7 @@ run.MulticoreFuture <- function(future, ...) { ) appendToFutureJournal(future, - step = "getWorker", + event = "getWorker", start = t_start, stop = Sys.time() ) diff --git a/R/journal.R b/R/journal.R index 6385aa86..a86e36e7 100644 --- a/R/journal.R +++ b/R/journal.R @@ -1,4 +1,4 @@ -#' Gets a journal of events for a future +#' Gets the logged journal of events for a future #' #' @param x A [Future] object. #' @@ -9,22 +9,37 @@ #' @param \ldots Not used. #' #' @return -#' A data frame with columns: +#' A data frame of class `FutureJournal` with columns: #' -#' 1. `step` (character string) +#' 1. `event` (character string) #' 2. `start` (POSIXct) #' 3. `at` (difftime) #' 4. `duration` (difftime) #' 5. `future_label` (character string) #' 6. `future_uuid` (character string) #' 7. `session_uuid` (character string) -#' +#' +#' Possible events are: +#' +#' * `create` - the future was created +#' * `launch` - the future was launched (aka run) +#' * `evaluate` - the future was evaluated +#' * `resolved` - the future was queried (may be occur multiple times) +#' * `gather` - the results was retrieved +#' #' The data frame is sorted by the `at` time. -#' Note that the timestamps for the `evaluate` step are based on the local +#' Note that the timestamps for the `evaluate` event are based on the local #' time on the worker. The system clocks on the worker and the calling R #' system may be out of sync. #' +#' @section Enabling and disabling event logging +#' To enable logging of events, set option `future.journal` is TRUE. +#' To disable, set it to FALSE (default). +#' #' @example incl/journal.R +#' +#' @keyword internal +#' @export journal <- function(x, ...) UseMethod("journal") #' @export @@ -42,10 +57,10 @@ journal.Future <- function(x, ...) { session_uuid <- rep(session_uuid, times = nrow(data)) ## Backward compatibility (until all backends does this) - if (!is.element("evaluate", data$step) && !is.null(x$result)) { + if (!is.element("evaluate", data$event) && !is.null(x$result)) { stop_if_not(is.character(session_uuid)) x <- appendToFutureJournal(x, - step = "evaluate", + event = "evaluate", start = x$result$started, stop = x$result$finished ) @@ -72,12 +87,12 @@ journal.Future <- function(x, ...) { ## Append session UUID data$session_uuid <- as.factor(session_uuid) - ## Coerce 'step' to a factor + ## Coerce 'event' to a factor known_levels <- c("lifespan", "create", "launch", "resolved", "gather", "evaluate") extra_levels <- c("attachPackages", "eraseWorker", "exportGlobals", "getWorker") - other_levels <- sort(setdiff(data$step, known_levels)) + other_levels <- sort(setdiff(data$event, known_levels)) levels <- c(known_levels, other_levels) - data$step <- factor(data$step, levels = levels) + data$event <- factor(data$event, levels = levels) ## Sort by relative start time if (nrow(data) > 1L) data <- data[order(data$at), ] @@ -128,38 +143,38 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { } -makeFutureJournal <- function(x, step = "create", start = stop, stop = Sys.time()) { +makeFutureJournal <- function(x, event = "create", start = stop, stop = Sys.time()) { stop_if_not( inherits(x, "Future"), is.null(x$.journal), - length(step) == 1L, is.character(step), + length(event) == 1L, is.character(event), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(step = step, start = start, stop = stop) + data <- data.frame(event = event, start = start, stop = stop) class(data) <- c("FutureJournal", class(data)) x$.journal <- data invisible(x) } -updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { +updateFutureJournal <- function(x, event, start = NULL, stop = Sys.time()) { ## Nothing to do? if (!inherits(x$.journal, "FutureJournal")) return(x) stop_if_not( inherits(x, "Future"), - length(step) == 1L, is.character(step), + length(event) == 1L, is.character(event), is.null(start) || (length(start) == 1L && inherits(start, "POSIXct")), is.null(stop) || (length(stop) == 1L && inherits(stop, "POSIXct")) ) data <- x$.journal stop_if_not(inherits(data, "FutureJournal")) - row <- which(data$step == step) + row <- which(data$event == event) n <- length(row) - if (n == 0L) stop("No such 'step' entry in journal: ", sQuote(step)) + if (n == 0L) stop("No such 'event' entry in journal: ", sQuote(event)) if (n > 1L) row <- row[n] entry <- data[row, ] if (!is.null(start)) entry$start <- start @@ -171,20 +186,20 @@ updateFutureJournal <- function(x, step, start = NULL, stop = Sys.time()) { } -appendToFutureJournal <- function(x, step, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { +appendToFutureJournal <- function(x, event, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { ## Nothing to do? if (!inherits(x$.journal, "FutureJournal")) return(x) - if (skip && is.element(step, x$.journal$step)) return(x) + if (skip && is.element(event, x$.journal$event)) return(x) stop_if_not( inherits(x, "Future"), - length(step) == 1L, is.character(step), + length(event) == 1L, is.character(event), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(step = step, start = start, stop = stop) + data <- data.frame(event = event, start = start, stop = stop) x$.journal <- rbind(x$.journal, data) invisible(x) } diff --git a/R/resolve.R b/R/resolve.R index 251b620c..4ec47ca3 100644 --- a/R/resolve.R +++ b/R/resolve.R @@ -60,7 +60,7 @@ resolve.Future <- function(x, idxs = NULL, recursive = 0, result = FALSE, stdout t_start <- Sys.time() on.exit({ appendToFutureJournal(x, - step = "resolve", + event = "resolve", start = t_start, stop = Sys.time(), skip = FALSE diff --git a/R/resolved.R b/R/resolved.R index c93bb3f5..1475b43b 100644 --- a/R/resolved.R +++ b/R/resolved.R @@ -25,7 +25,7 @@ resolved <- function(x, ...) { start <- Sys.time() on.exit({ appendToFutureJournal(x, - step = "resolved", + event = "resolved", start = start, stop = Sys.time(), skip = FALSE diff --git a/man/journal.Rd b/man/journal.Rd index 8cb8e703..6a8f4ee4 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -12,9 +12,9 @@ journal(x, ...) \item{\ldots}{Not used.} } \value{ -A data frame with columns: +A data frame of class \code{FutureJournal} with columns: \enumerate{ -\item \code{step} (character string) +\item \code{event} (character string) \item \code{start} (POSIXct) \item \code{at} (difftime) \item \code{duration} (difftime) @@ -23,8 +23,17 @@ A data frame with columns: \item \code{session_uuid} (character string) } +Possible events are: +\itemize{ +\item \code{create} - the future was created +\item \code{launch} - the future was launched (aka run) +\item \code{evaluate} - the future was evaluated +\item \code{resolved} - the future was queried (may be occur multiple times) +\item \code{gather} - the results was retrieved +} + The data frame is sorted by the \code{at} time. -Note that the timestamps for the \code{evaluate} step are based on the local +Note that the timestamps for the \code{evaluate} event are based on the local time on the worker. The system clocks on the worker and the calling R system may be out of sync. } From 8c8d3330f2cc89285363919ef53d962360c23027 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 3 Jun 2022 19:04:30 -0700 Subject: [PATCH 29/88] Moved gather_journals() from prototype package 'future.tools' --- DESCRIPTION | 2 +- NAMESPACE | 2 ++ R/gather_journals.R | 34 +++++++++++++++++++++++++++++++ R/journal.R | 7 +++++-- incl/gather_journals.R | 15 ++++++++++++++ man/gather_journals.Rd | 45 ++++++++++++++++++++++++++++++++++++++++++ man/journal.Rd | 14 +++++++++++-- 7 files changed, 114 insertions(+), 5 deletions(-) create mode 100644 R/gather_journals.R create mode 100644 incl/gather_journals.R create mode 100644 man/gather_journals.Rd diff --git a/DESCRIPTION b/DESCRIPTION index a3b0091a..c401094d 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9103 +Version: 1.26.1-9104 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NAMESPACE b/NAMESPACE index c15e78b7..211e481f 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -121,8 +121,10 @@ export(futureCall) export(futureOf) export(futureSessionInfo) export(futures) +export(gather_journals) export(getExpression) export(getGlobalsAndPackages) +export(journal) export(makeClusterMPI) export(makeClusterPSOCK) export(makeNodePSOCK) diff --git a/R/gather_journals.R b/R/gather_journals.R new file mode 100644 index 00000000..1c6d4fca --- /dev/null +++ b/R/gather_journals.R @@ -0,0 +1,34 @@ +#' Evaluate an R expression while collecting journals from completed futures +#' +#' @param expr The R expression to evaluate +#' +#' @param substitute If TRUE, then `expr` is subtituted, otherwise not. +#' +#' @param envir The environment where `expr` should be evaluated +#' +#' @details +#' This function evaluates an R expression and gathers the journals +#' signaled by futures as they are completed. A future journal comprise +#' a log of events appearing during the life-span of a future, e.g. +#' the timestamps when the future was created, launched, queried, +#' resolved, and its results are collected. +#' +#' @return +#' A list of \link[journal]{FutureJournal}:s. +#' +#' @example incl/gather_journals.R +#' +#' @export +gather_journals <- function(expr, substitute = TRUE, envir = parent.frame()) { + oopts <- options(future.journal = TRUE) + on.exit(options(oopts)) + + journals <- NULL + withCallingHandlers({ + eval(expr, envir = envir) + }, FutureJournalCondition = function(cond) { + journals <<- c(journals, list(cond$journal)) + }) + + journals +} diff --git a/R/journal.R b/R/journal.R index a86e36e7..9238e3c4 100644 --- a/R/journal.R +++ b/R/journal.R @@ -32,13 +32,16 @@ #' time on the worker. The system clocks on the worker and the calling R #' system may be out of sync. #' -#' @section Enabling and disabling event logging +#' @section Enabling and disabling event logging: #' To enable logging of events, set option `future.journal` is TRUE. #' To disable, set it to FALSE (default). #' #' @example incl/journal.R #' -#' @keyword internal +#' @seealso +#' Use [gather_journals()] to capture journals from all futures. +#' +#' @keywords internal #' @export journal <- function(x, ...) UseMethod("journal") diff --git a/incl/gather_journals.R b/incl/gather_journals.R new file mode 100644 index 00000000..8c30c9e1 --- /dev/null +++ b/incl/gather_journals.R @@ -0,0 +1,15 @@ +library(future.apply) + +slow_fcn <- function(x) { + Sys.sleep(x / 10) + sqrt(x) +} + +plan(multisession, workers = 2) +js <- gather_journals({ + vs <- future_lapply(3:1, FUN = slow_fcn) +}) +print(js) + +## Shut down parallel workers +plan(sequential) diff --git a/man/gather_journals.Rd b/man/gather_journals.Rd new file mode 100644 index 00000000..58af30dd --- /dev/null +++ b/man/gather_journals.Rd @@ -0,0 +1,45 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/gather_journals.R +\name{gather_journals} +\alias{gather_journals} +\title{Evaluate an R expression while collecting journals from completed futures} +\usage{ +gather_journals(expr, substitute = TRUE, envir = parent.frame()) +} +\arguments{ +\item{expr}{The R expression to evaluate} + +\item{substitute}{If TRUE, then \code{expr} is subtituted, otherwise not.} + +\item{envir}{The environment where \code{expr} should be evaluated} +} +\value{ +A list of \link[journal]{FutureJournal}:s. +} +\description{ +Evaluate an R expression while collecting journals from completed futures +} +\details{ +This function evaluates an R expression and gathers the journals +signaled by futures as they are completed. A future journal comprise +a log of events appearing during the life-span of a future, e.g. +the timestamps when the future was created, launched, queried, +resolved, and its results are collected. +} +\examples{ +library(future.apply) + +slow_fcn <- function(x) { + Sys.sleep(x / 10) + sqrt(x) +} + +plan(multisession, workers = 2) +js <- gather_journals({ + vs <- future_lapply(3:1, FUN = slow_fcn) +}) +print(js) + +## Shut down parallel workers +plan(sequential) +} diff --git a/man/journal.Rd b/man/journal.Rd index 6a8f4ee4..739ea753 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -2,7 +2,7 @@ % Please edit documentation in R/journal.R \name{journal} \alias{journal} -\title{Gets a journal of events for a future} +\title{Gets the logged journal of events for a future} \usage{ journal(x, ...) } @@ -38,8 +38,14 @@ time on the worker. The system clocks on the worker and the calling R system may be out of sync. } \description{ -Gets a journal of events for a future +Gets the logged journal of events for a future } +\section{Enabling and disabling event logging}{ + +To enable logging of events, set option \code{future.journal} is TRUE. +To disable, set it to FALSE (default). +} + \examples{ library(future) journal <- future:::journal @@ -59,3 +65,7 @@ print(js) plan(sequential) options(oopts) } +\seealso{ +Use \code{\link[=gather_journals]{gather_journals()}} to capture journals from all futures. +} +\keyword{internal} From 244c798b633e4c0cf8d7b9bb8696f94c1aac0bb4 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 3 Jun 2022 19:15:23 -0700 Subject: [PATCH 30/88] JOURNALS: Rename gather_journals() to capture_journals() --- NAMESPACE | 2 +- R/{gather_journals.R => capture_journals.R} | 10 ++++----- R/journal.R | 2 +- .../{gather_journals.R => capture_journals.R} | 7 +++---- incl/journal.R | 5 +---- ...gather_journals.Rd => capture_journals.Rd} | 21 +++++++++---------- man/journal.Rd | 7 ++----- 7 files changed, 23 insertions(+), 31 deletions(-) rename R/{gather_journals.R => capture_journals.R} (71%) rename incl/{gather_journals.R => capture_journals.R} (61%) rename man/{gather_journals.Rd => capture_journals.Rd} (63%) diff --git a/NAMESPACE b/NAMESPACE index 211e481f..0d293c97 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -114,6 +114,7 @@ export(autoStopCluster) export(availableCores) export(availableWorkers) export(backtrace) +export(capture_journals) export(cluster) export(future) export(futureAssign) @@ -121,7 +122,6 @@ export(futureCall) export(futureOf) export(futureSessionInfo) export(futures) -export(gather_journals) export(getExpression) export(getGlobalsAndPackages) export(journal) diff --git a/R/gather_journals.R b/R/capture_journals.R similarity index 71% rename from R/gather_journals.R rename to R/capture_journals.R index 1c6d4fca..672f9981 100644 --- a/R/gather_journals.R +++ b/R/capture_journals.R @@ -7,19 +7,19 @@ #' @param envir The environment where `expr` should be evaluated #' #' @details -#' This function evaluates an R expression and gathers the journals -#' signaled by futures as they are completed. A future journal comprise +#' This function evaluates an R expression and capture the journals +#' signaled by futures as they are completed. A future [journal] comprise #' a log of events appearing during the life-span of a future, e.g. #' the timestamps when the future was created, launched, queried, #' resolved, and its results are collected. #' #' @return -#' A list of \link[journal]{FutureJournal}:s. +#' A list of \link[=journal]{FutureJournal}:s. #' -#' @example incl/gather_journals.R +#' @example incl/capture_journals.R #' #' @export -gather_journals <- function(expr, substitute = TRUE, envir = parent.frame()) { +capture_journals <- function(expr, substitute = TRUE, envir = parent.frame()) { oopts <- options(future.journal = TRUE) on.exit(options(oopts)) diff --git a/R/journal.R b/R/journal.R index 9238e3c4..9a4f641e 100644 --- a/R/journal.R +++ b/R/journal.R @@ -39,7 +39,7 @@ #' @example incl/journal.R #' #' @seealso -#' Use [gather_journals()] to capture journals from all futures. +#' Use [capture_journals()] to capture journals from all futures. #' #' @keywords internal #' @export diff --git a/incl/gather_journals.R b/incl/capture_journals.R similarity index 61% rename from incl/gather_journals.R rename to incl/capture_journals.R index 8c30c9e1..b2668516 100644 --- a/incl/gather_journals.R +++ b/incl/capture_journals.R @@ -1,13 +1,12 @@ -library(future.apply) - slow_fcn <- function(x) { Sys.sleep(x / 10) sqrt(x) } plan(multisession, workers = 2) -js <- gather_journals({ - vs <- future_lapply(3:1, FUN = slow_fcn) +js <- capture_journals({ + fs <- lapply(3:1, FUN = function(x) future(slow_fcn(x))) + value(fs) }) print(js) diff --git a/incl/journal.R b/incl/journal.R index 0670e7c1..836a053b 100644 --- a/incl/journal.R +++ b/incl/journal.R @@ -1,6 +1,3 @@ -library(future) -journal <- future:::journal - ## Enable journaling of futures oopts <- options(future.journal = TRUE) @@ -12,6 +9,6 @@ vs <- value(fs) js <- lapply(fs, FUN = journal, baseline = t_start) print(js) -## Stop parallel workers and undo journaling settings +## Stop parallel workers and disable journal logging and signaling plan(sequential) options(oopts) diff --git a/man/gather_journals.Rd b/man/capture_journals.Rd similarity index 63% rename from man/gather_journals.Rd rename to man/capture_journals.Rd index 58af30dd..fc0f3925 100644 --- a/man/gather_journals.Rd +++ b/man/capture_journals.Rd @@ -1,10 +1,10 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/gather_journals.R -\name{gather_journals} -\alias{gather_journals} +% Please edit documentation in R/capture_journals.R +\name{capture_journals} +\alias{capture_journals} \title{Evaluate an R expression while collecting journals from completed futures} \usage{ -gather_journals(expr, substitute = TRUE, envir = parent.frame()) +capture_journals(expr, substitute = TRUE, envir = parent.frame()) } \arguments{ \item{expr}{The R expression to evaluate} @@ -14,29 +14,28 @@ gather_journals(expr, substitute = TRUE, envir = parent.frame()) \item{envir}{The environment where \code{expr} should be evaluated} } \value{ -A list of \link[journal]{FutureJournal}:s. +A list of \link[=journal]{FutureJournal}:s. } \description{ Evaluate an R expression while collecting journals from completed futures } \details{ -This function evaluates an R expression and gathers the journals -signaled by futures as they are completed. A future journal comprise +This function evaluates an R expression and capture the journals +signaled by futures as they are completed. A future \link{journal} comprise a log of events appearing during the life-span of a future, e.g. the timestamps when the future was created, launched, queried, resolved, and its results are collected. } \examples{ -library(future.apply) - slow_fcn <- function(x) { Sys.sleep(x / 10) sqrt(x) } plan(multisession, workers = 2) -js <- gather_journals({ - vs <- future_lapply(3:1, FUN = slow_fcn) +js <- capture_journals({ + fs <- lapply(3:1, FUN = function(x) future(slow_fcn(x))) + value(fs) }) print(js) diff --git a/man/journal.Rd b/man/journal.Rd index 739ea753..c38039dd 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -47,9 +47,6 @@ To disable, set it to FALSE (default). } \examples{ -library(future) -journal <- future:::journal - ## Enable journaling of futures oopts <- options(future.journal = TRUE) @@ -61,11 +58,11 @@ vs <- value(fs) js <- lapply(fs, FUN = journal, baseline = t_start) print(js) -## Stop parallel workers and undo journaling settings +## Stop parallel workers and disable journal logging and signaling plan(sequential) options(oopts) } \seealso{ -Use \code{\link[=gather_journals]{gather_journals()}} to capture journals from all futures. +Use \code{\link[=capture_journals]{capture_journals()}} to capture journals from all futures. } \keyword{internal} From 97834346d1a012dafc1810a140a4922c6cf5813f Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 3 Jun 2022 19:33:12 -0700 Subject: [PATCH 31/88] journal(): add warning that one must not depend on this function in other packages until further notice [ci skip] --- R/journal.R | 3 +++ man/journal.Rd | 3 ++- 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/R/journal.R b/R/journal.R index 9a4f641e..b856ebff 100644 --- a/R/journal.R +++ b/R/journal.R @@ -1,5 +1,8 @@ #' Gets the logged journal of events for a future #' +#' _WARNING: This function is under development. It can change at any time. +#' For now, please, do not depend on this function in a published R package._ +#' #' @param x A [Future] object. #' ## @param baseline (POSIXct; optional) A timestamp to server as time zero diff --git a/man/journal.Rd b/man/journal.Rd index c38039dd..107bba43 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -38,7 +38,8 @@ time on the worker. The system clocks on the worker and the calling R system may be out of sync. } \description{ -Gets the logged journal of events for a future +\emph{WARNING: This function is under development. It can change at any time. +For now, please, do not depend on this function in a published R package.} } \section{Enabling and disabling event logging}{ From ab4ac8c74e05df4733138b8bbac18d798e585532 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 8 Jun 2022 17:43:26 -0700 Subject: [PATCH 32/88] JOURNAL: Add 'type' field --- R/Future-class.R | 2 ++ R/future.R | 2 +- R/journal.R | 38 ++++++++++++++++++++++++++------------ R/resolve.R | 1 + R/resolved.R | 1 + man/journal.Rd | 24 ++++++++++++++++++------ 6 files changed, 49 insertions(+), 19 deletions(-) diff --git a/R/Future-class.R b/R/Future-class.R index c4715d3f..aca95ff7 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -471,6 +471,7 @@ run <- function(future, ...) { on.exit({ appendToFutureJournal(future, event = "launch", + type = "overhead", start = start, stop = Sys.time() ) @@ -490,6 +491,7 @@ result <- function(future, ...) { on.exit({ appendToFutureJournal(future, event = "gather", + type = "overhead", start = start, stop = Sys.time() ) diff --git a/R/future.R b/R/future.R index e4e8ded9..87bff1a2 100644 --- a/R/future.R +++ b/R/future.R @@ -219,7 +219,7 @@ future <- function(expr, envir = parent.frame(), substitute = TRUE, lazy = FALSE ## Enable journaling? if (getOption("future.journal", FALSE)) { - future <- makeFutureJournal(future, start = t_start) + future <- makeFutureJournal(future, event = "create", type = "overhead", start = t_start) } if (!lazy) { diff --git a/R/journal.R b/R/journal.R index b856ebff..13ee3e0a 100644 --- a/R/journal.R +++ b/R/journal.R @@ -15,6 +15,7 @@ #' A data frame of class `FutureJournal` with columns: #' #' 1. `event` (character string) +#' 1. `type` (character string) #' 2. `start` (POSIXct) #' 3. `at` (difftime) #' 4. `duration` (difftime) @@ -22,13 +23,23 @@ #' 6. `future_uuid` (character string) #' 7. `session_uuid` (character string) #' -#' Possible events are: +#' Common events are: #' -#' * `create` - the future was created -#' * `launch` - the future was launched (aka run) -#' * `evaluate` - the future was evaluated -#' * `resolved` - the future was queried (may be occur multiple times) -#' * `gather` - the results was retrieved +#' * `create` - the future was created (an `overhead`) +#' * `launch` - the future was launched (an `overhead`) +#' * `evaluate` - the future was evaluated (an `evaluation`) +#' * `resolved` - the future was queried (may be occur multiple times) (an `overhead`) +#' * `gather` - the results was retrieved (an `overhead`) +#' +#' but others may be added by other Future classes. +#' +#' Common event types are: +#' +#' * `evaluation` - processing time is spent on evaluation +#' * `overhead` - processing time is spent on orchestrating the future +#' * `querying` - processing time is spent on polling the future +#' +#' but others may be added by other Future classes. #' #' The data frame is sorted by the `at` time. #' Note that the timestamps for the `evaluate` event are based on the local @@ -67,6 +78,7 @@ journal.Future <- function(x, ...) { stop_if_not(is.character(session_uuid)) x <- appendToFutureJournal(x, event = "evaluate", + type = "evaluation", start = x$result$started, stop = x$result$finished ) @@ -149,29 +161,30 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { } -makeFutureJournal <- function(x, event = "create", start = stop, stop = Sys.time()) { +makeFutureJournal <- function(x, event = "create", type = "other", start = stop, stop = Sys.time()) { stop_if_not( inherits(x, "Future"), is.null(x$.journal), length(event) == 1L, is.character(event), + length(type) == 1L, is.character(type), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(event = event, start = start, stop = stop) + data <- data.frame(event = event, type = type, start = start, stop = stop) class(data) <- c("FutureJournal", class(data)) x$.journal <- data invisible(x) } - -updateFutureJournal <- function(x, event, start = NULL, stop = Sys.time()) { +updateFutureJournal <- function(x, event, type = "other", start = NULL, stop = Sys.time()) { ## Nothing to do? if (!inherits(x$.journal, "FutureJournal")) return(x) stop_if_not( inherits(x, "Future"), length(event) == 1L, is.character(event), + length(type) == 1L, is.character(type), is.null(start) || (length(start) == 1L && inherits(start, "POSIXct")), is.null(stop) || (length(stop) == 1L && inherits(stop, "POSIXct")) ) @@ -192,7 +205,7 @@ updateFutureJournal <- function(x, event, start = NULL, stop = Sys.time()) { } -appendToFutureJournal <- function(x, event, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { +appendToFutureJournal <- function(x, event, type = "other", start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { ## Nothing to do? if (!inherits(x$.journal, "FutureJournal")) return(x) @@ -201,11 +214,12 @@ appendToFutureJournal <- function(x, event, start = Sys.time(), stop = as.POSIXc stop_if_not( inherits(x, "Future"), length(event) == 1L, is.character(event), + length(type) == 1L, is.character(type), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(event = event, start = start, stop = stop) + data <- data.frame(event = event, type = type, start = start, stop = stop) x$.journal <- rbind(x$.journal, data) invisible(x) } diff --git a/R/resolve.R b/R/resolve.R index 4ec47ca3..5bcdf0ab 100644 --- a/R/resolve.R +++ b/R/resolve.R @@ -61,6 +61,7 @@ resolve.Future <- function(x, idxs = NULL, recursive = 0, result = FALSE, stdout on.exit({ appendToFutureJournal(x, event = "resolve", + type = "overhead", start = t_start, stop = Sys.time(), skip = FALSE diff --git a/R/resolved.R b/R/resolved.R index 1475b43b..dae2b1ff 100644 --- a/R/resolved.R +++ b/R/resolved.R @@ -26,6 +26,7 @@ resolved <- function(x, ...) { on.exit({ appendToFutureJournal(x, event = "resolved", + type = "querying", start = start, stop = Sys.time(), skip = FALSE diff --git a/man/journal.Rd b/man/journal.Rd index 107bba43..d81a799c 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -15,6 +15,7 @@ journal(x, ...) A data frame of class \code{FutureJournal} with columns: \enumerate{ \item \code{event} (character string) +\item \code{type} (character string) \item \code{start} (POSIXct) \item \code{at} (difftime) \item \code{duration} (difftime) @@ -23,15 +24,26 @@ A data frame of class \code{FutureJournal} with columns: \item \code{session_uuid} (character string) } -Possible events are: +Common events are: \itemize{ -\item \code{create} - the future was created -\item \code{launch} - the future was launched (aka run) -\item \code{evaluate} - the future was evaluated -\item \code{resolved} - the future was queried (may be occur multiple times) -\item \code{gather} - the results was retrieved +\item \code{create} - the future was created (an \code{overhead}) +\item \code{launch} - the future was launched (an \code{overhead}) +\item \code{evaluate} - the future was evaluated (an \code{evaluation}) +\item \code{resolved} - the future was queried (may be occur multiple times) (an \code{overhead}) +\item \code{gather} - the results was retrieved (an \code{overhead}) } +but others may be added by other Future classes. + +Common event types are: +\itemize{ +\item \code{evaluation} - processing time is spent on evaluation +\item \code{overhead} - processing time is spent on orchestrating the future +\item \code{querying} - processing time is spent on polling the future +} + +but others may be added by other Future classes. + The data frame is sorted by the \code{at} time. Note that the timestamps for the \code{evaluate} event are based on the local time on the worker. The system clocks on the worker and the calling R From 42a2c69d6292d63495b3de28303265d1e540236e Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 8 Jun 2022 21:53:40 -0700 Subject: [PATCH 33/88] Add 'type' and 'parent' fields to future journals --- DESCRIPTION | 2 +- R/ClusterFuture-class.R | 32 +++++++++++++++++++------------ R/Future-class.R | 8 ++++---- R/MulticoreFuture-class.R | 8 +++++--- R/journal.R | 40 ++++++++++++++++++++------------------- man/journal.Rd | 3 ++- 6 files changed, 53 insertions(+), 40 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index c401094d..9edd2020 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9104 +Version: 1.26.1-9105 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 61594329..1b108607 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -129,9 +129,11 @@ run.ClusterFuture <- function(future, ...) { cl <- workers[node_idx] appendToFutureJournal(future, - event = "getWorker", - start = t_start, - stop = Sys.time() + event = "getWorker", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) @@ -143,9 +145,11 @@ run.ClusterFuture <- function(future, ...) { t_start <- Sys.time() cluster_call(cl, fun = grmall, future = future, when = "call grmall() on") appendToFutureJournal(future, - event = "eraseWorker", - start = t_start, - stop = Sys.time() + event = "eraseWorker", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) } @@ -166,9 +170,11 @@ run.ClusterFuture <- function(future, ...) { length(packages), hpaste(sQuote(packages)), node_idx) } appendToFutureJournal(future, - event = "attachPackages", - start = t_start, - stop = Sys.time() + event = "attachPackages", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) ## (iii) Export globals @@ -198,9 +204,11 @@ run.ClusterFuture <- function(future, ...) { } if (debug) mdebugf("Exporting %d global objects (%s) to cluster node #%d ... DONE", length(globals), total_size, node_idx) appendToFutureJournal(future, - event = "exportGlobals", - start = t_start, - stop = Sys.time() + event = "exportGlobals", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) } ## Not needed anymore diff --git a/R/Future-class.R b/R/Future-class.R index aca95ff7..fe638760 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -471,9 +471,9 @@ run <- function(future, ...) { on.exit({ appendToFutureJournal(future, event = "launch", - type = "overhead", + type = "overhead", start = start, - stop = Sys.time() + stop = Sys.time() ) }) } @@ -491,9 +491,9 @@ result <- function(future, ...) { on.exit({ appendToFutureJournal(future, event = "gather", - type = "overhead", + type = "overhead", start = start, - stop = Sys.time() + stop = Sys.time() ) ## Signal FutureJournalCondition? diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index 53148c03..85ec8c2f 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -83,9 +83,11 @@ run.MulticoreFuture <- function(future, ...) { ) appendToFutureJournal(future, - event = "getWorker", - start = t_start, - stop = Sys.time() + event = "getWorker", + type = "other", + parent = "launch", + start = t_start, + stop = Sys.time() ) ## Add to registry diff --git a/R/journal.R b/R/journal.R index 13ee3e0a..9f824044 100644 --- a/R/journal.R +++ b/R/journal.R @@ -15,13 +15,14 @@ #' A data frame of class `FutureJournal` with columns: #' #' 1. `event` (character string) -#' 1. `type` (character string) -#' 2. `start` (POSIXct) -#' 3. `at` (difftime) -#' 4. `duration` (difftime) -#' 5. `future_label` (character string) -#' 6. `future_uuid` (character string) -#' 7. `session_uuid` (character string) +#' 2. `type` (character string) +#' 3. `parent` (character string) +#' 4. `start` (POSIXct) +#' 5. `at` (difftime) +#' 6. `duration` (difftime) +#' 7. `future_label` (character string) +#' 8. `future_uuid` (character string) +#' 9. `session_uuid` (character string) #' #' Common events are: #' @@ -37,7 +38,7 @@ #' #' * `evaluation` - processing time is spent on evaluation #' * `overhead` - processing time is spent on orchestrating the future -#' * `querying` - processing time is spent on polling the future +#' * `waiting` - processing time is spent on waiting to set up or querying the future #' #' but others may be added by other Future classes. #' @@ -161,30 +162,30 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { } -makeFutureJournal <- function(x, event = "create", type = "other", start = stop, stop = Sys.time()) { +makeFutureJournal <- function(x, event = "create", type = "other", parent = NA_character_, start = stop, stop = Sys.time()) { stop_if_not( inherits(x, "Future"), is.null(x$.journal), - length(event) == 1L, is.character(event), - length(type) == 1L, is.character(type), + length(event) == 1L, is.character(event), !is.na(event), + length(type) == 1L, is.character(type), !is.na(event), + length(parent) == 1L, is.character(parent), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(event = event, type = type, start = start, stop = stop) + data <- data.frame(event = event, type = type, parent = parent, start = start, stop = stop) class(data) <- c("FutureJournal", class(data)) x$.journal <- data invisible(x) } -updateFutureJournal <- function(x, event, type = "other", start = NULL, stop = Sys.time()) { +updateFutureJournal <- function(x, event, start = NULL, stop = Sys.time()) { ## Nothing to do? if (!inherits(x$.journal, "FutureJournal")) return(x) stop_if_not( inherits(x, "Future"), - length(event) == 1L, is.character(event), - length(type) == 1L, is.character(type), + length(event) == 1L, is.character(event), !is.na(event), is.null(start) || (length(start) == 1L && inherits(start, "POSIXct")), is.null(stop) || (length(stop) == 1L && inherits(stop, "POSIXct")) ) @@ -205,7 +206,7 @@ updateFutureJournal <- function(x, event, type = "other", start = NULL, stop = S } -appendToFutureJournal <- function(x, event, type = "other", start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { +appendToFutureJournal <- function(x, event, type = "other", parent = NA_character_, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { ## Nothing to do? if (!inherits(x$.journal, "FutureJournal")) return(x) @@ -213,13 +214,14 @@ appendToFutureJournal <- function(x, event, type = "other", start = Sys.time(), stop_if_not( inherits(x, "Future"), - length(event) == 1L, is.character(event), - length(type) == 1L, is.character(type), + length(event) == 1L, is.character(event), !is.na(event), + length(type) == 1L, is.character(type), !is.na(event), + length(parent) == 1L, is.character(parent), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(event = event, type = type, start = start, stop = stop) + data <- data.frame(event = event, type = type, parent = parent, start = start, stop = stop) x$.journal <- rbind(x$.journal, data) invisible(x) } diff --git a/man/journal.Rd b/man/journal.Rd index d81a799c..cc1ed592 100644 --- a/man/journal.Rd +++ b/man/journal.Rd @@ -16,6 +16,7 @@ A data frame of class \code{FutureJournal} with columns: \enumerate{ \item \code{event} (character string) \item \code{type} (character string) +\item \code{parent} (character string) \item \code{start} (POSIXct) \item \code{at} (difftime) \item \code{duration} (difftime) @@ -39,7 +40,7 @@ Common event types are: \itemize{ \item \code{evaluation} - processing time is spent on evaluation \item \code{overhead} - processing time is spent on orchestrating the future -\item \code{querying} - processing time is spent on polling the future +\item \code{waiting} - processing time is spent on waiting to set up or querying the future } but others may be added by other Future classes. From 07660166edf091f12018e276450730adee52a938 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 8 Jun 2022 23:05:51 -0700 Subject: [PATCH 34/88] Add summary() for FutureJournal and print() for FutureJournalSummary --- NAMESPACE | 2 + R/journal.R | 92 +++++++++++++++++++++++++++++++++++++++++ incl/capture_journals.R | 5 ++- man/capture_journals.Rd | 5 ++- 4 files changed, 102 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 0d293c97..8449821d 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -38,6 +38,7 @@ S3method(plot,Mandelbrot) S3method(print,Future) S3method(print,FutureCondition) S3method(print,FutureJournal) +S3method(print,FutureJournalSummary) S3method(print,FutureResult) S3method(print,FutureStrategy) S3method(print,FutureStrategyList) @@ -69,6 +70,7 @@ S3method(run,ConstantFuture) S3method(run,Future) S3method(run,MulticoreFuture) S3method(run,UniprocessFuture) +S3method(summary,FutureJournal) S3method(tweak,"function") S3method(tweak,character) S3method(tweak,future) diff --git a/R/journal.R b/R/journal.R index 9f824044..b9671cac 100644 --- a/R/journal.R +++ b/R/journal.R @@ -162,6 +162,98 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { } +#' @export +summary.FutureJournal <- function(object, ...) { + dt_top <- subset(object, is.na(parent)) + + uuids <- unique(dt_top$future_uuid) + nbr_of_futures <- length(uuids) + + ## Calculate 'stop' times + dt_top$stop <- dt_top$start + dt_top$duration + + ## ------------------------------------------------------- + ## 1. Calculate the total walltime + ## ------------------------------------------------------- + ## (a) timestamp when the first event starts + t_begin <- subset(dt_top, event == "create")[["start"]] + ## (b) timestamp when 'gather' finishes + t_end <- subset(dt_top, event == "gather")[["stop"]] + ## (c) durations (per future) + t_delta <- t_end - t_begin + ## (d) total duration + t_total <- sum(t_delta, na.rm = TRUE) + + ## (e) build table + t <- NULL + if (length(uuids) > 1L) { + t <- c(t, min = min(t_delta, na.rm = TRUE)) + t <- c(t, mean = mean(t_delta, na.rm = TRUE)) + t <- c(t, median = median(t_delta, na.rm = TRUE)) + t <- c(t, max = max(t_delta, na.rm = TRUE)) + } + t <- c(t, total = t_total) + stats <- data.frame(walltime = t) + + ## ------------------------------------------------------- + ## 2. Calculate efficiency + ## ------------------------------------------------------- + ## (a) Per future + eff <- list() + for (kk in seq_along(uuids)) { + uuid <- uuids[[kk]] + dt_uuid <- subset(dt_top, future_uuid == uuid) + res <- data.frame( + evaluate = subset(dt_uuid, type == "evaluation")[["duration"]], + overhead = sum(subset(dt_uuid, type == "overhead")[["duration"]]) + ) + res[["duration"]] <- t_delta[kk] + eff[[uuid]] <- res + } + eff <- Reduce(rbind, eff) + + ## (b) Summary + res <- NULL + if (length(uuids) > 1L) { + t <- lapply(c("min", "mean", "median", "max"), FUN = function(fcn_name) { + fcn <- get(fcn_name, mode = "function") + t <- as.data.frame(lapply(eff, FUN = fcn)) + rownames(t) <- fcn_name + t + }) + t <- Reduce(rbind, t) + res <- t + } + + ## (c) Total + t <- as.data.frame(lapply(eff, FUN = sum)) + rownames(t) <- "total" + res <- rbind(res, t) + + ## (d) Combine + stats <- cbind(stats, res) + + ## (e) Fractions + stats[["evaluate_ratio"]] <- as.numeric(stats[["evaluate"]]) / as.numeric(stats[["duration"]]) + stats[["overhead_ratio"]] <- as.numeric(stats[["overhead"]]) / as.numeric(stats[["duration"]]) + + stats[["summary"]] <- rownames(stats) + rownames(stats) <- NULL + stats <- stats[, c("summary", "evaluate", "evaluate_ratio", "overhead", "overhead_ratio", "duration", "walltime")] + + attr(stats, "nbr_of_futures") <- length(uuids) + class(stats) <- c("FutureJournalSummary", class(stats)) + stats +} + + +#' @export +print.FutureJournalSummary <- function(x, ...) { + cat(sprintf("Number of futures: %d\n", attr(x, "nbr_of_futures"))) + NextMethod("print") +} + + makeFutureJournal <- function(x, event = "create", type = "other", parent = NA_character_, start = stop, stop = Sys.time()) { stop_if_not( inherits(x, "Future"), diff --git a/incl/capture_journals.R b/incl/capture_journals.R index b2668516..5f2a2e43 100644 --- a/incl/capture_journals.R +++ b/incl/capture_journals.R @@ -8,7 +8,10 @@ js <- capture_journals({ fs <- lapply(3:1, FUN = function(x) future(slow_fcn(x))) value(fs) }) -print(js) + +## Summarize all journals +js_all <- Reduce(rbind, js) +print(summary(js_all), digits = 2L) ## Shut down parallel workers plan(sequential) diff --git a/man/capture_journals.Rd b/man/capture_journals.Rd index fc0f3925..c012f78c 100644 --- a/man/capture_journals.Rd +++ b/man/capture_journals.Rd @@ -37,7 +37,10 @@ js <- capture_journals({ fs <- lapply(3:1, FUN = function(x) future(slow_fcn(x))) value(fs) }) -print(js) + +## Summarize all journals +js_all <- Reduce(rbind, js) +print(summary(js_all), digits = 2L) ## Shut down parallel workers plan(sequential) From 8321ce756a24b78d113cc665017f32d080df6e8b Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 8 Jun 2022 23:20:58 -0700 Subject: [PATCH 35/88] Fix: 'walltime' field lost 'difftime' class --- R/journal.R | 1 + 1 file changed, 1 insertion(+) diff --git a/R/journal.R b/R/journal.R index b9671cac..d84be28b 100644 --- a/R/journal.R +++ b/R/journal.R @@ -191,6 +191,7 @@ summary.FutureJournal <- function(object, ...) { t <- c(t, mean = mean(t_delta, na.rm = TRUE)) t <- c(t, median = median(t_delta, na.rm = TRUE)) t <- c(t, max = max(t_delta, na.rm = TRUE)) + t <- as.difftime(t, units = "secs") } t <- c(t, total = t_total) stats <- data.frame(walltime = t) From 70cc4e7485d2531bbbf80f6e925245148586a54a Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sat, 11 Jun 2022 18:07:24 -0700 Subject: [PATCH 36/88] CLEANUP: Drop argument 'index' for journal() for 'list' --- DESCRIPTION | 2 +- R/journal.R | 17 ++++++++--------- 2 files changed, 9 insertions(+), 10 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 9edd2020..3f2636fc 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9105 +Version: 1.26.1-9106 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/journal.R b/R/journal.R index d84be28b..3f2be46d 100644 --- a/R/journal.R +++ b/R/journal.R @@ -130,7 +130,7 @@ journal.FutureJournal <- function(x, baseline = NULL, ...) { } #' @export -journal.list <- function(x, index = seq_along(x), baseline = TRUE, ...) { +journal.list <- function(x, baseline = TRUE, ...) { ## Reset relative time zero to the first observed timestamp? if (isTRUE(baseline)) { stop_if_not(baseline >= 1L, baseline <= length(x)) @@ -142,15 +142,11 @@ journal.list <- function(x, index = seq_along(x), baseline = TRUE, ...) { js <- lapply(x, FUN = journal, baseline = baseline, ...) - ## Add index? - if (!is.null(index)) { - stop_if_not(length(index) == length(x)) - js <- lapply(index, FUN = function(idx) { - cbind(index = idx, js[[idx]]) - }) - } + class <- class(js[[1]]) + js <- Reduce(rbind, js) + class(js) <- class - Reduce(rbind, js) + js } @@ -164,6 +160,9 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { #' @export summary.FutureJournal <- function(object, ...) { + ## To please 'R CMD check' + event <- future_uuid <- median <- parent <- type <- NULL + dt_top <- subset(object, is.na(parent)) uuids <- unique(dt_top$future_uuid) From 5abda36bea18628ec84d69450ceff9a8f75a11e1 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 12 Jun 2022 17:06:13 -0700 Subject: [PATCH 37/88] The recorded 'finished' time of FutureResult is now set at the very end of the expanded future expression, after all undoing of options etc. is done --- DESCRIPTION | 2 +- R/expressions.R | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 3f2636fc..f8f9c4de 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9106 +Version: 1.26.1-9107 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/expressions.R b/R/expressions.R index 3688a5b6..a5d8c692 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -287,6 +287,7 @@ makeExpression <- local({ } ...future.result$conditions <- ...future.conditions + ...future.result$finished <- base::Sys.time() ...future.result }) From 8f81020e2b3ca13caef290789f8d4ab499421cf7 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 21 Jun 2022 10:36:17 -0700 Subject: [PATCH 38/88] BETA: Make capture_journals() private for now --- DESCRIPTION | 2 +- NAMESPACE | 1 - R/capture_journals.R | 3 ++- man/capture_journals.Rd | 47 ----------------------------------------- 4 files changed, 3 insertions(+), 50 deletions(-) delete mode 100644 man/capture_journals.Rd diff --git a/DESCRIPTION b/DESCRIPTION index f8f9c4de..94c3850e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9107 +Version: 1.26.1-9108 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NAMESPACE b/NAMESPACE index 8449821d..822eef0b 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -116,7 +116,6 @@ export(autoStopCluster) export(availableCores) export(availableWorkers) export(backtrace) -export(capture_journals) export(cluster) export(future) export(futureAssign) diff --git a/R/capture_journals.R b/R/capture_journals.R index 672f9981..05d2cc3c 100644 --- a/R/capture_journals.R +++ b/R/capture_journals.R @@ -18,7 +18,8 @@ #' #' @example incl/capture_journals.R #' -#' @export +#' @keywords internal +#' @noRd capture_journals <- function(expr, substitute = TRUE, envir = parent.frame()) { oopts <- options(future.journal = TRUE) on.exit(options(oopts)) diff --git a/man/capture_journals.Rd b/man/capture_journals.Rd deleted file mode 100644 index c012f78c..00000000 --- a/man/capture_journals.Rd +++ /dev/null @@ -1,47 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/capture_journals.R -\name{capture_journals} -\alias{capture_journals} -\title{Evaluate an R expression while collecting journals from completed futures} -\usage{ -capture_journals(expr, substitute = TRUE, envir = parent.frame()) -} -\arguments{ -\item{expr}{The R expression to evaluate} - -\item{substitute}{If TRUE, then \code{expr} is subtituted, otherwise not.} - -\item{envir}{The environment where \code{expr} should be evaluated} -} -\value{ -A list of \link[=journal]{FutureJournal}:s. -} -\description{ -Evaluate an R expression while collecting journals from completed futures -} -\details{ -This function evaluates an R expression and capture the journals -signaled by futures as they are completed. A future \link{journal} comprise -a log of events appearing during the life-span of a future, e.g. -the timestamps when the future was created, launched, queried, -resolved, and its results are collected. -} -\examples{ -slow_fcn <- function(x) { - Sys.sleep(x / 10) - sqrt(x) -} - -plan(multisession, workers = 2) -js <- capture_journals({ - fs <- lapply(3:1, FUN = function(x) future(slow_fcn(x))) - value(fs) -}) - -## Summarize all journals -js_all <- Reduce(rbind, js) -print(summary(js_all), digits = 2L) - -## Shut down parallel workers -plan(sequential) -} From 3a156477ab600bda7282bad54a9e04c2f0a26a86 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 21 Jun 2022 10:46:00 -0700 Subject: [PATCH 39/88] BETA: Make journal() private for now --- DESCRIPTION | 2 +- NAMESPACE | 1 - R/journal.R | 2 +- man/journal.Rd | 82 -------------------------------------------------- 4 files changed, 2 insertions(+), 85 deletions(-) delete mode 100644 man/journal.Rd diff --git a/DESCRIPTION b/DESCRIPTION index 94c3850e..75f2806a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9108 +Version: 1.26.1-9109 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NAMESPACE b/NAMESPACE index 822eef0b..5bb68567 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -125,7 +125,6 @@ export(futureSessionInfo) export(futures) export(getExpression) export(getGlobalsAndPackages) -export(journal) export(makeClusterMPI) export(makeClusterPSOCK) export(makeNodePSOCK) diff --git a/R/journal.R b/R/journal.R index 3f2be46d..b0ee7369 100644 --- a/R/journal.R +++ b/R/journal.R @@ -57,7 +57,7 @@ #' Use [capture_journals()] to capture journals from all futures. #' #' @keywords internal -#' @export +#' @noRd journal <- function(x, ...) UseMethod("journal") #' @export diff --git a/man/journal.Rd b/man/journal.Rd deleted file mode 100644 index cc1ed592..00000000 --- a/man/journal.Rd +++ /dev/null @@ -1,82 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/journal.R -\name{journal} -\alias{journal} -\title{Gets the logged journal of events for a future} -\usage{ -journal(x, ...) -} -\arguments{ -\item{x}{A \link{Future} object.} - -\item{\ldots}{Not used.} -} -\value{ -A data frame of class \code{FutureJournal} with columns: -\enumerate{ -\item \code{event} (character string) -\item \code{type} (character string) -\item \code{parent} (character string) -\item \code{start} (POSIXct) -\item \code{at} (difftime) -\item \code{duration} (difftime) -\item \code{future_label} (character string) -\item \code{future_uuid} (character string) -\item \code{session_uuid} (character string) -} - -Common events are: -\itemize{ -\item \code{create} - the future was created (an \code{overhead}) -\item \code{launch} - the future was launched (an \code{overhead}) -\item \code{evaluate} - the future was evaluated (an \code{evaluation}) -\item \code{resolved} - the future was queried (may be occur multiple times) (an \code{overhead}) -\item \code{gather} - the results was retrieved (an \code{overhead}) -} - -but others may be added by other Future classes. - -Common event types are: -\itemize{ -\item \code{evaluation} - processing time is spent on evaluation -\item \code{overhead} - processing time is spent on orchestrating the future -\item \code{waiting} - processing time is spent on waiting to set up or querying the future -} - -but others may be added by other Future classes. - -The data frame is sorted by the \code{at} time. -Note that the timestamps for the \code{evaluate} event are based on the local -time on the worker. The system clocks on the worker and the calling R -system may be out of sync. -} -\description{ -\emph{WARNING: This function is under development. It can change at any time. -For now, please, do not depend on this function in a published R package.} -} -\section{Enabling and disabling event logging}{ - -To enable logging of events, set option \code{future.journal} is TRUE. -To disable, set it to FALSE (default). -} - -\examples{ -## Enable journaling of futures -oopts <- options(future.journal = TRUE) - -plan(multisession, workers = 2L) - -t_start <- Sys.time() -fs <- lapply(1:3, FUN = function(x) future({ Sys.sleep(x); sqrt(x) })) -vs <- value(fs) -js <- lapply(fs, FUN = journal, baseline = t_start) -print(js) - -## Stop parallel workers and disable journal logging and signaling -plan(sequential) -options(oopts) -} -\seealso{ -Use \code{\link[=capture_journals]{capture_journals()}} to capture journals from all futures. -} -\keyword{internal} From fd6df9190455136ef076f84d010f26b068545432 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 21 Jun 2022 22:28:27 -0700 Subject: [PATCH 40/88] ClusterFuture now logs 'receiveResult' events --- DESCRIPTION | 2 +- R/ClusterFuture-class.R | 10 ++++++++++ R/journal.R | 2 +- 3 files changed, 12 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 75f2806a..96448fcd 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9109 +Version: 1.26.1-9110 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 1b108607..816745b0 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -394,6 +394,8 @@ receiveMessageFromWorker <- function(future, ...) { } } + t_start <- Sys.time() + ## If not, wait for process to finish, and ## then collect and record the value msg <- NULL @@ -440,6 +442,14 @@ receiveMessageFromWorker <- function(future, ...) { if (inherits(msg, "FutureResult")) { result <- msg + appendToFutureJournal(future, + event = "receiveResult", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() + ) + ## Add back already signaled and muffled conditions so that also ## they will be resignaled each time value() is called. signaled <- future$.signaledConditions diff --git a/R/journal.R b/R/journal.R index b0ee7369..792778b2 100644 --- a/R/journal.R +++ b/R/journal.R @@ -108,7 +108,7 @@ journal.Future <- function(x, ...) { ## Coerce 'event' to a factor known_levels <- c("lifespan", "create", "launch", "resolved", "gather", "evaluate") - extra_levels <- c("attachPackages", "eraseWorker", "exportGlobals", "getWorker") + extra_levels <- c("attachPackages", "eraseWorker", "exportGlobals", "receiveResult", "getWorker") other_levels <- sort(setdiff(data$event, known_levels)) levels <- c(known_levels, other_levels) data$event <- factor(data$event, levels = levels) From f5bf1d8411a6005cca46151cb2e1fd679003aa3a Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 21 Jun 2022 22:36:30 -0700 Subject: [PATCH 41/88] Don't call journaling functions, unless enabled --- DESCRIPTION | 2 +- R/ClusterFuture-class.R | 82 ++++++++++++++++++++++----------------- R/Future-class.R | 3 +- R/MulticoreFuture-class.R | 16 ++++---- R/resolve.R | 23 ++++++----- R/resolved.R | 3 +- 6 files changed, 74 insertions(+), 55 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 96448fcd..f86576df 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.26.1-9110 +Version: 1.26.1-9111 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 816745b0..01a5e520 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -128,13 +128,15 @@ run.ClusterFuture <- function(future, ...) { ## Cluster node to use cl <- workers[node_idx] - appendToFutureJournal(future, - event = "getWorker", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() - ) + if (inherits(future$.journal, "FutureJournal")) { + appendToFutureJournal(future, + event = "getWorker", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() + ) + } ## (i) Reset global environment of cluster node such that @@ -144,13 +146,15 @@ run.ClusterFuture <- function(future, ...) { if (!persistent) { t_start <- Sys.time() cluster_call(cl, fun = grmall, future = future, when = "call grmall() on") - appendToFutureJournal(future, - event = "eraseWorker", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() - ) + if (inherits(future$.journal, "FutureJournal")) { + appendToFutureJournal(future, + event = "eraseWorker", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() + ) + } } @@ -169,13 +173,16 @@ run.ClusterFuture <- function(future, ...) { if (debug) mdebugf("Attaching %d packages (%s) on cluster node #%d ... DONE", length(packages), hpaste(sQuote(packages)), node_idx) } - appendToFutureJournal(future, - event = "attachPackages", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() - ) + + if (inherits(future$.journal, "FutureJournal")) { + appendToFutureJournal(future, + event = "attachPackages", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() + ) + } ## (iii) Export globals globals <- globals(future) @@ -203,13 +210,16 @@ run.ClusterFuture <- function(future, ...) { value <- NULL } if (debug) mdebugf("Exporting %d global objects (%s) to cluster node #%d ... DONE", length(globals), total_size, node_idx) - appendToFutureJournal(future, - event = "exportGlobals", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() - ) + + if (inherits(future$.journal, "FutureJournal")) { + appendToFutureJournal(future, + event = "exportGlobals", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() + ) + } } ## Not needed anymore globals <- NULL @@ -442,13 +452,15 @@ receiveMessageFromWorker <- function(future, ...) { if (inherits(msg, "FutureResult")) { result <- msg - appendToFutureJournal(future, - event = "receiveResult", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() - ) + if (inherits(future$.journal, "FutureJournal")) { + appendToFutureJournal(future, + event = "receiveResult", + type = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() + ) + } ## Add back already signaled and muffled conditions so that also ## they will be resignaled each time value() is called. diff --git a/R/Future-class.R b/R/Future-class.R index fe638760..ee38fa29 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -466,7 +466,8 @@ run.Future <- function(future, ...) { #' @keywords internal run <- function(future, ...) { ## Automatically update journal entries for Future object - if (inherits(future, "Future")) { + if (inherits(future, "Future") && + inherits(future$.journal, "FutureJournal")) { start <- Sys.time() on.exit({ appendToFutureJournal(future, diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index 85ec8c2f..bf513287 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -82,13 +82,15 @@ run.MulticoreFuture <- function(future, ...) { workers = future$workers ) - appendToFutureJournal(future, - event = "getWorker", - type = "other", - parent = "launch", - start = t_start, - stop = Sys.time() - ) + if (inherits(future$.journal, "FutureJournal")) { + appendToFutureJournal(future, + event = "getWorker", + type = "other", + parent = "launch", + start = t_start, + stop = Sys.time() + ) + } ## Add to registry FutureRegistry(reg, action = "add", future = future, earlySignal = TRUE) diff --git a/R/resolve.R b/R/resolve.R index 5bcdf0ab..08b29787 100644 --- a/R/resolve.R +++ b/R/resolve.R @@ -57,16 +57,19 @@ resolve.Future <- function(x, idxs = NULL, recursive = 0, result = FALSE, stdout } ## Automatically update journal entries for Future object - t_start <- Sys.time() - on.exit({ - appendToFutureJournal(x, - event = "resolve", - type = "overhead", - start = t_start, - stop = Sys.time(), - skip = FALSE - ) - }) + if (inherits(future, "Future") && + inherits(future$.journal, "FutureJournal")) { + t_start <- Sys.time() + on.exit({ + appendToFutureJournal(x, + event = "resolve", + type = "overhead", + start = t_start, + stop = Sys.time(), + skip = FALSE + ) + }) + } if (is.logical(recursive)) { if (recursive) recursive <- getOption("future.resolve.recursive", 99) diff --git a/R/resolved.R b/R/resolved.R index dae2b1ff..89129528 100644 --- a/R/resolved.R +++ b/R/resolved.R @@ -21,7 +21,8 @@ #' @export resolved <- function(x, ...) { ## Automatically update journal entries for Future object - if (inherits(x, "Future")) { + if (inherits(future, "Future") && + inherits(future$.journal, "FutureJournal")) { start <- Sys.time() on.exit({ appendToFutureJournal(x, From 0954a085ad250fef43a4cfe2f5e71e41f6856f54 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 21 Jun 2022 23:18:42 -0700 Subject: [PATCH 42/88] 'receiveResult' is a child of 'gather' --- R/ClusterFuture-class.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 01a5e520..b016e2cb 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -456,7 +456,7 @@ receiveMessageFromWorker <- function(future, ...) { appendToFutureJournal(future, event = "receiveResult", type = "overhead", - parent = "launch", + parent = "gather", start = t_start, stop = Sys.time() ) From 90367c3ee236c1056a5c80ed498cfcdb9a8f24b8 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Feb 2023 08:55:50 -0800 Subject: [PATCH 43/88] Bump develop version [ci skip] --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 40773735..b789f46e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0 +Version: 1.31.0-9000 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NEWS.md b/NEWS.md index fa66112c..299d3c72 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,8 @@ +# Version (development version) + + * ... + + # Version 1.31.0 [2023-01-31] ## Signficant Changes From 546e5c806b7e98152d346e336784f6bcb0a9e554 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Feb 2023 10:41:21 -0800 Subject: [PATCH 44/88] REVDEP: 276 packages [ci skip] --- revdep/README.md | 34 +++++++++++++++++----------------- revdep/problems.md | 45 ++------------------------------------------- 2 files changed, 19 insertions(+), 60 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 516f65ca..6f70200a 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,23 +1,23 @@ # Platform -|field |value | -|:--------|:-----------------------------------------------------| -|version |R version 4.2.2 (2022-10-31) | -|os |CentOS Linux 7 (Core) | -|system |x86_64, linux-gnu | -|ui |X11 | -|language |en | -|collate |en_US.UTF-8 | -|ctype |en_US.UTF-8 | -|tz |America/Los_Angeles | -|date |2023-01-30 | -|pandoc |3.0 @ /software/c4/cbi/software/pandoc-3.0/bin/pandoc | +|field |value | +|:--------|:---------------------------------------------------------| +|version |R version 4.2.2 (2022-10-31) | +|os |CentOS Linux 7 (Core) | +|system |x86_64, linux-gnu | +|ui |X11 | +|language |en | +|collate |en_US.UTF-8 | +|ctype |en_US.UTF-8 | +|tz |America/Los_Angeles | +|date |2023-02-01 | +|pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.30.0 |1.30.0-9026 |* | +|future |1.31.0 |1.30.0-9026 |* | |codetools |0.2-18 |0.2-18 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -161,7 +161,7 @@ |LWFBrook90R |0.5.2 | | | | |[MAI](problems.md#mai) |1.4.0 | | |1 | |MAMS |2.0.0 | | | | -|[marginaleffects](problems.md#marginaleffects)|0.8.1 |1 | | | +|marginaleffects |0.9.0 | | | | |mcmcensemble |3.0.0 | | | | |mcp |0.3.2 | | | | |merTools |0.5.2 | | | | @@ -216,7 +216,7 @@ |progressr |0.13.0 | | | | |[projpred](problems.md#projpred)|2.3.0 | | |1 | |[promises](problems.md#promises)|1.2.0.1 | | |1 | -|Prostar |1.30.2 | | | | +|Prostar |1.30.3 | | | | |protti |0.6.0 | | | | |PSCBS |0.66.0 | | | | |PUMP |1.0.1 | | | | @@ -236,7 +236,7 @@ |[rgee](problems.md#rgee) |1.1.5 | | |2 | |[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | |robust2sls |0.2.2 | | | | -|RTransferEntropy |0.2.14 | | | | +|RTransferEntropy |0.2.21 | | | | |[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | |scBubbletree |1.0.0 | | | | |[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | @@ -254,7 +254,7 @@ |sigminer |2.1.9 | | | | |Signac |1.9.0 | | | | |[signeR](problems.md#signer)|2.0.2 | | |3 | -|[SimDesign](problems.md#simdesign)|2.10 | | |2 | +|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | |simfinapi |0.2.0 | | | | |simglm |0.8.9 | | | | |simhelpers |0.1.2 | | | | diff --git a/revdep/problems.md b/revdep/problems.md index ab10ced2..4ae3bc68 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1467,47 +1467,6 @@ Run `revdep_details(, "MAI")` for more info is not mentioned in the DESCRIPTION file. ``` -# marginaleffects - -
- -* Version: 0.8.1 -* GitHub: https://github.com/vincentarelbundock/marginaleffects -* Source code: https://github.com/cran/marginaleffects -* Date/Publication: 2022-11-23 22:20:06 UTC -* Number of recursive dependencies: 348 - -Run `revdep_details(, "marginaleffects")` for more info - -
- -## In both - -* checking examples ... ERROR - ``` - Running examples in ‘marginaleffects-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_cco - > ### Title: Plot Conditional Contrasts - > ### Aliases: plot_cco - > - > ### ** Examples - > - > mod <- lm(mpg ~ hp * drat * factor(am), data = mtcars) - ... - > plot_cco(mod, effect = "hp", condition = "drat") - > - > plot_cco(mod, effect = "hp", condition = c("drat", "am")) - > - > plot_cco(mod, effect = "hp", condition = list("am", "drat" = 3:5)) - Error: Unable to compute predicted values with this model. You can try to - supply a different dataset to the `newdata` argument. If this does not - work, you can file a report on the Github Issue Tracker: - https://github.com/vincentarelbundock/marginaleffects/issues - Execution halted - ``` - # metabolomicsR
@@ -2626,10 +2585,10 @@ Run `revdep_details(, "signeR")` for more info
-* Version: 2.10 +* Version: 2.10.1 * GitHub: https://github.com/philchalmers/SimDesign * Source code: https://github.com/cran/SimDesign -* Date/Publication: 2023-01-24 17:10:02 UTC +* Date/Publication: 2023-02-01 15:30:02 UTC * Number of recursive dependencies: 104 Run `revdep_details(, "SimDesign")` for more info From 8b9e64d7e1d6cb6d38edd38a221adb881ce866e0 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Feb 2023 12:27:40 -0800 Subject: [PATCH 45/88] TESTS: more clues if assertion on envvar undoing fails --- DESCRIPTION | 2 +- tests/future,optsenvvars.R | 30 ++++++++++++++++++++++++++---- 2 files changed, 27 insertions(+), 5 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index b789f46e..5795748e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9000 +Version: 1.31.0-9001 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/tests/future,optsenvvars.R b/tests/future,optsenvvars.R index 1897f717..525487a0 100644 --- a/tests/future,optsenvvars.R +++ b/tests/future,optsenvvars.R @@ -30,17 +30,39 @@ for (strategy in strategies) { identical(Sys.getenv("R_DEFAULT_INTERNET_TIMEOUT"), "300") #DISABLED# is.na(Sys.getenv("ABC", NA_character_)) ) + + envvars <- Sys.getenv() if (.Platform$OS.type == "windows") { ## Drop empty environment variables, because they are not supported by ## MS Windows, but may exist because they're inherited from a host OS old_envvars <- old_envvars[nzchar(old_envvars)] - envvars <- Sys.getenv() envvars <- envvars[nzchar(envvars)] - stopifnot(identical(envvars[names(old_envvars)], old_envvars)) - } else { - stopifnot(identical(Sys.getenv()[names(old_envvars)], old_envvars)) } + envvars <- envvars[names(old_envvars)] + + ## Any added? + diff <- setdiff(names(envvars), names(old_envvars)) + if (length(diff) > 0) { + stop(sprintf("Detected added environment variables: %s", paste(diff, collapse = ", "))) + } + + ## Any removed? + diff <- setdiff(names(old_envvars), names(envvars)) + if (length(diff) > 0) { + stop(sprintf("Detected removed environment variables: %s", paste(diff, collapse = ", "))) + } + + ## Any changed? + for (name in names(old_envvars)) { + if (!identical(envvars[[name]], old_envvars[[name]])) { + stop(sprintf("Detected modified environment variable: %s=%s (was %s)", name, sQuote(envvars[[name]]), sQuote(old_envvars[[name]]))) + } + } + + stopifnot(all.equal(envvars, old_envvars)) + stopifnot(identical(envvars, old_envvars)) + message(sprintf("- plan('%s') ... DONE", strategy)) } ## for (strategy ...) From a0170c2d4865c9859ac4c1aaf3ffc2c853e94007 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Feb 2023 13:24:15 -0800 Subject: [PATCH 46/88] Allow for multiprocess() to call .Defunct() [#546] --- DESCRIPTION | 2 +- R/multiprocess.R | 17 ++++++++++++++++- 2 files changed, 17 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 5795748e..538b339b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9001 +Version: 1.31.0-9002 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/multiprocess.R b/R/multiprocess.R index 09506538..7269a04b 100644 --- a/R/multiprocess.R +++ b/R/multiprocess.R @@ -22,7 +22,22 @@ #' #' @export multiprocess <- function(..., workers = availableCores(), envir = parent.frame()) { - .Deprecated(msg = sprintf("Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.")) + + fmtstr <- "Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is %s in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'." + defunct <- getOption("future.deprecated.defunct") + if (is.element("multiprocess", defunct)) { + msg <- sprintf(fmtstr, "defunct") + ## Need to wrap .Defunct() in another frame to avoid: + ## Error in as.vector(x, "character") : + ## cannot coerce type 'closure' to vector of type 'character' + dfcn <- function(...) .Defunct(...) + } else { + msg <- sprintf(fmtstr, "deprecated") + msg <- paste(msg, "Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.") + dfcn <- .Deprecated + } + dfcn(msg = msg, package = .packageName) + sequential(..., envir = envir) } class(multiprocess) <- c("sequential", "uniprocess", "future", "function") From 89c41ebe1b5a8be279f016792676e204d13711b7 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Feb 2023 16:44:46 -0800 Subject: [PATCH 47/88] tweak deprecation/defunct messages [ci skip] --- R/multiprocess.R | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/R/multiprocess.R b/R/multiprocess.R index 7269a04b..d4e4abdc 100644 --- a/R/multiprocess.R +++ b/R/multiprocess.R @@ -23,17 +23,17 @@ #' @export multiprocess <- function(..., workers = availableCores(), envir = parent.frame()) { - fmtstr <- "Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is %s in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'." + msg1 <- "Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30]." + msg2 <- "Instead, specify either 'multisession' (recommended) or 'multicore'." defunct <- getOption("future.deprecated.defunct") if (is.element("multiprocess", defunct)) { - msg <- sprintf(fmtstr, "defunct") + msg <- paste(msg1, "It will soon become defunct, i.e. produce an error.", msg2) ## Need to wrap .Defunct() in another frame to avoid: ## Error in as.vector(x, "character") : ## cannot coerce type 'closure' to vector of type 'character' dfcn <- function(...) .Defunct(...) } else { - msg <- sprintf(fmtstr, "deprecated") - msg <- paste(msg, "Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.") + msg <- paste(msg1, msg2, "Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.") dfcn <- .Deprecated } dfcn(msg = msg, package = .packageName) From 43b570587b9232e64becba6b78b4a873d6409e87 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Feb 2023 17:49:52 -0800 Subject: [PATCH 48/88] REVDEP: 276 packages with R_FUTURE_DEPRECATED_DEFUNCT=multiprocess => 5 broken packages [ci skip] --- .../README.md | 581 ++-- .../cran.md | 31 +- .../problems.md | 2382 ++++++++--------- 3 files changed, 1376 insertions(+), 1618 deletions(-) diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/README.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/README.md index 2b7f10c8..6ad4e20c 100644 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/README.md +++ b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/README.md @@ -1,290 +1,319 @@ # Platform -|field |value | -|:--------|:-------------------------------------------------------| -|version |R version 4.1.3 (2022-03-10) | -|os |CentOS Linux 7 (Core) | -|system |x86_64, linux-gnu | -|ui |X11 | -|language |en | -|collate |en_US.UTF-8 | -|ctype |en_US.UTF-8 | -|tz |America/Los_Angeles | -|date |2022-04-28 | -|pandoc |2.18 @ /software/c4/cbi/software/pandoc-2.18/bin/pandoc | +|field |value | +|:--------|:---------------------------------------------------------| +|version |R version 4.2.2 (2022-10-31) | +|os |CentOS Linux 7 (Core) | +|system |x86_64, linux-gnu | +|ui |X11 | +|language |en | +|collate |en_US.UTF-8 | +|ctype |en_US.UTF-8 | +|tz |America/Los_Angeles | +|date |2023-02-01 | +|pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.25.0 |1.25.0-9004 |* | -|codetools |0.2-18 |0.2-18 | | -|digest |0.6.29 |0.6.29 | | -|globals |0.14.0 |0.14.0 | | -|listenv |0.8.0 |0.8.0 | | -|parallelly |1.31.1 |1.31.1 | | +|future |1.31.0 |1.31.0-9002 |* | +|codetools |0.2-19 |0.2-19 | | +|digest |0.6.31 |0.6.31 | | +|globals |0.16.2 |0.16.2 | | +|listenv |0.9.0 |0.9.0 | | +|parallelly |1.34.0 |1.34.0 | | # Revdeps -## New problems (13) +## New problems (5) -|package |version |error |warning |note | -|:------------------------------------------------|:-------|:------|:-------|:----| -|[alookr](problems.md#alookr) |0.3.5 |__+1__ | | | -|[AlpsNMR](problems.md#alpsnmr) |3.4.0 | |__+1__ |1 | -|[blockCV](problems.md#blockcv) |2.1.4 |__+1__ |__+1__ |2 | -|[dhReg](problems.md#dhreg) |0.1.1 |__+1__ | | | -|[EpiNow2](problems.md#epinow2) |1.3.2 |__+1__ | |2 | -|[greta](problems.md#greta) |0.4.2 |__+1__ | | | -|[ipc](problems.md#ipc) |0.1.3 | |__+1__ |1 | -|[kernelboot](problems.md#kernelboot) |0.1.7 |__+1__ | |1 | -|[MineICA](problems.md#mineica) |1.34.0 |__+1__ |2 |5 | -|[prewas](problems.md#prewas) |1.1.1 |__+1__ |__+1__ |1 | -|[progressr](problems.md#progressr) |0.10.0 |__+1__ | | | -|[rBiasCorrection](problems.md#rbiascorrection) |0.3.3 |__+1__ | | | -|[RTransferEntropy](problems.md#rtransferentropy) |0.2.14 | |__+1__ | | +|package |version |error |warning |note | +|:-------|:-------|:------|:-------|:----| +|[blockCV](problems.md#blockcv)|2.1.4 |__+2__ | |2 | +|[dhReg](problems.md#dhreg)|0.1.1 |__+1__ | | | +|[fiery](problems.md#fiery)|1.1.4 |__+1__ | | | +|[MineICA](problems.md#mineica)|1.38.0 |__+1__ |3 |4 | +|[prewas](problems.md#prewas)|1.1.1 |__+2__ | |1 | -## All (239) +## All (276) -|package |version |error |warning |note | -|:--------------------------------------------------------|:---------|:------|:-------|:----| -|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | -|[alookr](problems.md#alookr) |0.3.5 |__+1__ | | | -|[AlpsNMR](problems.md#alpsnmr) |3.4.0 | |__+1__ |1 | -|arkdb |0.0.15 | | | | -|aroma.affymetrix |3.2.0 | | | | -|[aroma.core](problems.md#aromacore) |3.2.2 | | |1 | -|[BAMBI](problems.md#bambi) |2.3.3 | | |2 | -|[baseballr](problems.md#baseballr) |1.2.0 | | |1 | -|[BatchGetSymbols](problems.md#batchgetsymbols) |2.6.1 | | |1 | -|batchtools |0.9.15 | | | | -|bayesian |0.0.8 | | | | -|bayesmove |0.2.1 | | | | -|[bcmaps](problems.md#bcmaps) |1.0.2 | | |1 | -|[BEKKs](problems.md#bekks) |1.1.0 | | |2 | -|bhmbasket |0.9.5 | | | | -|[bigDM](problems.md#bigdm) |0.4.1 | | |2 | -|[bistablehistory](problems.md#bistablehistory) |1.1.1 | | |3 | -|bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan) |0.4-1 | | |2 | -|[blockCV](problems.md#blockcv) |2.1.4 |__+1__ |__+1__ |2 | -|bolasso |0.1.0 | | | | -|[brms](problems.md#brms) |2.17.0 | | |2 | -|ceRNAnetsim |1.6.99 | | | | -|[cfbfastR](problems.md#cfbfastr) |1.6.4 | | |1 | -|[ChromSCape](problems.md#chromscape) |1.4.0 | | |5 | -|[civis](problems.md#civis) |3.0.0 | | |1 | -|Clustering |1.7.6 | | | | -|codalm |0.1.2 | | | | -|[codebook](problems.md#codebook) |0.9.2 | | |3 | -|conformalInference.fd |1.1.1 | | | | -|conformalInference.multi |1.1.1 | | | | -|crossmap |0.3.0 | | | | -|[cSEM](problems.md#csem) |0.4.0 | | |1 | -|[CSGo](problems.md#csgo) |0.6.7 | | |1 | -|cvCovEst |1.0.2 | | | | -|[datapackage.r](problems.md#datapackager) |1.3.5 |1 | |1 | -|DeclareDesign |0.30.0 | | | | -|[delayed](problems.md#delayed) |0.3.0 | | |2 | -|[dhReg](problems.md#dhreg) |0.1.1 |__+1__ | | | -|[dipsaus](problems.md#dipsaus) |0.2.0 | | |1 | -|disk.frame |0.7.2 | | | | -|[dispositionEffect](problems.md#dispositioneffect) |1.0.0 |1 | | | -|doFuture |0.12.2 | | | | -|DQAstats |0.2.6 | | | | -|[dragon](problems.md#dragon) |1.2.1 | | |1 | -|drake |7.13.3 | | | | -|drimmR |1.0.1 | | | | -|drtmle |1.1.1 | | | | -|[easyalluvial](problems.md#easyalluvial) |0.3.0 | | |1 | -|[EFAtools](problems.md#efatools) |0.4.1 | | |2 | -|elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.13 | |1 | | -|[EpiNow2](problems.md#epinow2) |1.3.2 |__+1__ | |2 | -|[epitweetr](problems.md#epitweetr) |2.0.3 | | |3 | -|epwshiftr |0.1.3 | | | | -|EWCE |1.2.0 | | | | -|ezcox |1.0.2 | | | | -|fabletools |0.3.2 | | | | -|FAMoS |0.3.0 | | | | -|fastpos |0.4.1 | | | | -|fastRhockey |0.3.0 | | | | -|fiery |1.1.3 | | | | -|finbif |0.6.4 | | | | -|[fipe](problems.md#fipe) |0.0.1 | | |1 | -|[flowGraph](problems.md#flowgraph) |1.2.0 | |1 |2 | -|[foieGras](problems.md#foiegras) |0.7-6 | | |1 | -|[forecastML](problems.md#forecastml) |0.9.0 | | |1 | -|fundiversity |0.2.1 | | | | -|funGp |0.2.2 | | | | -|furrr |0.2.3 | | | | -|future.apply |1.9.0 | | | | -|future.batchtools |0.10.0 | | | | -|future.callr |0.8.0 | | | | -|future.tests |0.3.0 | | | | -|fxTWAPLS |0.1.0 | | | | -|genBaRcode |1.2.4 | | | | -|[geocmeans](problems.md#geocmeans) |0.2.0 | | |2 | -|[GetBCBData](problems.md#getbcbdata) |0.6 | | |2 | -|[googleComputeEngineR](problems.md#googlecomputeenginer) |0.3.0 | | |1 | -|googlePubsubR |0.0.3 | | | | -|[googleTagManageR](problems.md#googletagmanager) |0.2.0 | | |1 | -|[grattan](problems.md#grattan) |1.9.0.10 | | |2 | -|[greed](problems.md#greed) |0.6.0 | | |2 | -|[greta](problems.md#greta) |0.4.2 |__+1__ | | | -|gstat |2.0-9 | | | | -|GSVA |1.42.0 | | | | -|gsynth |1.2.1 | | | | -|gtfs2gps |2.0-2 | | | | -|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews) |0.1.0 | | |1 | -|hacksig |0.1.2 | | | | -|[hal9001](problems.md#hal9001) |0.4.3 | | |1 | -|haldensify |0.2.3 | | | | -|hoopR |1.5.0 | | | | -|[hwep](problems.md#hwep) |0.0.1 | | |1 | -|idmodelr |0.3.2 | | | | -|IFAA |1.0.6 | | | | -|[iml](problems.md#iml) |0.10.1 | | |1 | -|[infercnv](problems.md#infercnv) |1.10.1 | | |2 | -|[inlinedocs](problems.md#inlinedocs) |2019.12.5 | | |1 | -|interflex |1.2.6 | | | | -|[ipc](problems.md#ipc) |0.1.3 | |__+1__ |1 | -|isoreader |1.3.2 | | | | -|[ivmte](problems.md#ivmte) |1.4.0 | | |1 | -|JointAI |1.0.3 | | | | -|jstor |0.3.10 | | | | -|JuliaConnectoR |1.1.1 | | | | -|[kernelboot](problems.md#kernelboot) |0.1.7 |__+1__ | |1 | -|[keyATM](problems.md#keyatm) |0.4.0 | | |1 | -|[lava](problems.md#lava) |1.6.10 | | |1 | -|ldaPrototype |0.3.1 | | | | -|ldsr |0.0.2 | | | | -|lemna |0.9.2 | | | | -|LexFindR |1.0.2 | | | | -|lgr |0.4.3 | | | | -|[lidR](problems.md#lidr) |4.0.0 |2 | |1 | -|lightr |1.6.2 | | | | -|[lmtp](problems.md#lmtp) |1.0.0 | | |1 | -|LWFBrook90R |0.4.5 | | | | -|[MAI](problems.md#mai) |1.0.0 | | |1 | -|MAMS |2.0.0 | | | | -|mcmcensemble |3.0.0 | | | | -|mcp |0.3.2 | | | | -|merTools |0.5.2 | | | | -|[microservices](problems.md#microservices) |0.1.2 |1 | |1 | -|microSTASIS |0.1.0 | | | | -|migraph |0.9.3 | | | | -|mikropml |1.2.2 | | | | -|[MineICA](problems.md#mineica) |1.34.0 |__+1__ |2 |5 | -|[missSBM](problems.md#misssbm) |1.0.2 | | |1 | -|mistyR |1.2.1 | | | | -|mlr3 |0.13.3 | | | | -|mlr3db |0.4.2 | | | | -|mlr3spatial |0.1.2 | | | | -|[momentuHMM](problems.md#momentuhmm) |1.5.4 | | |1 | -|MOSS |0.2.2 | | | | -|mrgsim.parallel |0.2.1 | | | | -|nfl4th |1.0.1 | | | | -|nflfastR |4.3.0 | | | | -|nflseedR |1.0.2 | | | | -|NMproject |0.6.7 | | | | -|[onemapsgapi](problems.md#onemapsgapi) |1.0.0 | | |1 | -|[OOS](problems.md#oos) |1.0.0 | | |1 | -|origami |1.0.5 | | | | -|[partR2](problems.md#partr2) |0.9.1 | | |1 | -|[pavo](problems.md#pavo) |2.7.1 | |1 | | -|PCRedux |1.1 | | | | -|PeakSegDisk |2022.2.1 | | | | -|penaltyLearning |2020.5.13 | | | | -|[photosynthesis](problems.md#photosynthesis) |2.0.1 |1 | |2 | -|[phylolm](problems.md#phylolm) |2.6.2 | | |1 | -|[PLNmodels](problems.md#plnmodels) |0.11.6 | | |1 | -|[plumber](problems.md#plumber) |1.1.0 | | |1 | -|[ppcseq](problems.md#ppcseq) |1.2.0 | | |3 | -|[ppseq](problems.md#ppseq) |0.1.1 | | |1 | -|[prewas](problems.md#prewas) |1.1.1 |__+1__ |__+1__ |1 | -|[progressr](problems.md#progressr) |0.10.0 |__+1__ | | | -|projpred |2.1.1 | | | | -|[promises](problems.md#promises) |1.2.0.1 | | |1 | -|[Prostar](problems.md#prostar) |1.26.4 | | |2 | -|protti |0.3.0 | | | | -|PSCBS |0.66.0 | | | | -|[PUMP](problems.md#pump) |1.0.0 | | |1 | -|[QDNAseq](problems.md#qdnaseq) |1.30.0 | | |1 | -|qgcomp |2.8.6 | | | | -|qgcompint |0.7.0 | | | | -|[RAINBOWR](problems.md#rainbowr) |0.1.29 | | |1 | -|rangeMapper |2.0.2 | | | | -|[rBiasCorrection](problems.md#rbiascorrection) |0.3.3 |__+1__ | | | -|refineR |1.0.0 | | | | -|[regmedint](problems.md#regmedint) |1.0.0 | | |1 | -|[remiod](problems.md#remiod) |1.0.0 | | |1 | -|reproducible |1.2.8 | | | | -|reval |3.0-0 | | | | -|[rgee](problems.md#rgee) |1.1.3 | | |2 | -|[robotstxt](problems.md#robotstxt) |0.7.13 | | |2 | -|robust2sls |0.2.0 | | | | -|[RTransferEntropy](problems.md#rtransferentropy) |0.2.14 | |__+1__ | | -|[sapfluxnetr](problems.md#sapfluxnetr) |0.1.3 | | |1 | -|[scDiffCom](problems.md#scdiffcom) |0.1.0 | | |1 | -|SCtools |0.3.1 | | | | -|[sctransform](problems.md#sctransform) |0.3.3 | | |1 | -|[sdmApp](problems.md#sdmapp) |0.0.2 | | |1 | -|[seer](problems.md#seer) |1.1.7 | | |1 | -|semtree |0.9.17 | | | | -|[sentopics](problems.md#sentopics) |0.6.2 | | |3 | -|[Seurat](problems.md#seurat) |4.1.0 | | |2 | -|shar |1.3.2 | | | | -|[shiny](problems.md#shiny) |1.7.1 | | |1 | -|[shiny.worker](problems.md#shinyworker) |0.0.1 | | |2 | -|[shinyrecap](problems.md#shinyrecap) |0.1.0 | | |2 | -|sigminer |2.1.4 | | | | -|Signac |1.6.0 | | | | -|simfinapi |0.2.0 | | | | -|simglm |0.8.9 | | | | -|[simhelpers](problems.md#simhelpers) |0.1.1 | | |1 | -|sims |0.0.3 | | | | -|skewlmm |1.0.0 | | | | -|[skpr](problems.md#skpr) |1.1.4 | | |1 | -|smoots |1.1.3 | | | | -|sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude) |1.1.3 | | |1 | -|sovereign |1.2.1 | | | | -|[spacey](problems.md#spacey) |0.1.1 | | |2 | -|[SpaDES.core](problems.md#spadescore) |1.0.10 |1 | | | -|[spaMM](problems.md#spamm) |3.11.14 | | |2 | -|[sparrpowR](problems.md#sparrpowr) |0.2.5 | |1 | | -|[SPARSEMODr](problems.md#sparsemodr) |1.1.0 | | |1 | -|[spatialTIME](problems.md#spatialtime) |1.2.0 | | |1 | -|[spatialwarnings](problems.md#spatialwarnings) |3.0.3 | |1 |1 | -|sperrorest |3.0.4 | | | | -|[sphunif](problems.md#sphunif) |1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork) |0.4.3.1 | | |1 | -|[ssdtools](problems.md#ssdtools) |1.0.1 | | |1 | -|[stars](problems.md#stars) |0.5-5 | | |2 | -|startR |2.2.0 | | | | -|steps |1.2.1 | | | | -|supercells |0.8.2 | | | | -|[synergyfinder](problems.md#synergyfinder) |3.2.10 | |2 |2 | -|[tableschema.r](problems.md#tableschemar) |1.1.1 | | |3 | -|[targeted](problems.md#targeted) |0.2.0 | | |1 | -|targets |0.12.0 | | | | -|tcensReg |0.1.7 | | | | -|tcplfit2 |0.1.3 | | | | -|tealeaves |1.0.5 | | | | -|[text](problems.md#text) |0.9.50 | | |1 | -|tglkmeans |0.3.4 | | | | -|tidyqwi |0.1.2 | | | | -|TKCat |0.7.1 | | | | -|[TreeSearch](problems.md#treesearch) |1.1.1 | | |1 | -|[TriDimRegression](problems.md#tridimregression) |1.0.1 | | |3 | -|[tsfeatures](problems.md#tsfeatures) |1.0.2 | | |1 | -|[TSstudio](problems.md#tsstudio) |0.1.6 | | |1 | -|[txshift](problems.md#txshift) |0.3.8 | | |1 | -|[UCSCXenaShiny](problems.md#ucscxenashiny) |1.1.7 | | |1 | -|[updog](problems.md#updog) |2.1.2 | | |1 | -|[vmeasur](problems.md#vmeasur) |0.1.4 | |1 | | -|wehoop |1.2.1 | | | | -|[XNAString](problems.md#xnastring) |1.2.2 | | |3 | +|package |version |error |warning |note | +|:------------------------|:---------|:------|:-------|:----| +|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | +|alookr |0.3.7 | | | | +|alphaci |1.0.0 | | | | +|[AlpsNMR](problems.md#alpsnmr)|4.0.2 |3 | | | +|arkdb |0.0.16 | | | | +|aroma.affymetrix |3.2.1 | | | | +|aroma.cn |1.7.0 | | | | +|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | +|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | +|bamm |0.4.3 | | | | +|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | +|BatchGetSymbols |2.6.4 | | | | +|[batchtools](problems.md#batchtools)|0.9.15 | | |2 | +|bayesian |0.0.9 | | | | +|bayesmove |0.2.1 | | | | +|bcmaps |1.1.0 | | | | +|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | +|bhmbasket |0.9.5 | | | | +|[bigDM](problems.md#bigdm)|0.5.0 | | |2 | +|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | +|bkmrhat |1.1.3 | | | | +|[blavaan](problems.md#blavaan)|0.4-3 | | |3 | +|[blockCV](problems.md#blockcv)|2.1.4 |__+2__ | |2 | +|bolasso |0.2.0 | | | | +|[brms](problems.md#brms) |2.18.0 | | |2 | +|brpop |0.1.5 | | | | +|canaper |1.0.0 | | | | +|ceRNAnetsim |1.10.0 | | | | +|cft |1.0.0 | | | | +|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | +|[civis](problems.md#civis)|3.0.0 | | |1 | +|Clustering |1.7.7 | | | | +|codalm |0.1.2 | | | | +|[codebook](problems.md#codebook)|0.9.2 | | |3 | +|conformalInference.fd |1.1.1 | | | | +|conformalInference.multi |1.1.1 | | | | +|crossmap |0.4.0 | | | | +|CSCNet |0.1.2 | | | | +|[cSEM](problems.md#csem) |0.5.0 | | |1 | +|[CSGo](problems.md#csgo) |0.6.7 | | |1 | +|cvCovEst |1.2.0 | | | | +|dagHMM |0.1.0 | | | | +|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | +|delayed |0.4.0 | | | | +|[dhReg](problems.md#dhreg)|0.1.1 |__+1__ | | | +|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | +|[disk.frame](problems.md#diskframe)|0.7.2 |1 | | | +|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | +|doFuture |0.12.2 | | | | +|DQAstats |0.3.2 | | | | +|[dragon](problems.md#dragon)|1.2.1 | | |1 | +|drake |7.13.4 | | | | +|drimmR |1.0.1 | | | | +|drtmle |1.1.2 | | | | +|dsos |0.1.1 | | | | +|DT |0.27 | | | | +|easyalluvial |0.3.1 | | | | +|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | +|elevatr |0.4.2 | | | | +|[envi](problems.md#envi) |0.1.15 | |1 | | +|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | +|epwshiftr |0.1.3 | | | | +|ezcox |1.0.2 | | | | +|fabletools |0.3.2 | | | | +|FAMoS |0.3.0 | | | | +|fastRhockey |0.4.0 | | | | +|[fect](problems.md#fect) |1.0.0 | | |2 | +|[fiery](problems.md#fiery)|1.1.4 |__+1__ | | | +|finbif |0.7.1 | | | | +|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | +|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | +|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | +|fst4pg |1.0.0 | | | | +|fundiversity |1.1.1 | | | | +|funGp |0.3.1 | | | | +|furrr |0.3.1 | | | | +|future.apply |1.10.0 | | | | +|future.batchtools |0.11.0 | | | | +|future.callr |0.8.1 | | | | +|future.tests |0.5.0 | | | | +|fxTWAPLS |0.1.2 | | | | +|genBaRcode |1.2.5 | | | | +|[geocmeans](problems.md#geocmeans)|0.3.2 | | |1 | +|GetBCBData |0.7.0 | | | | +|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | +|googlePubsubR |0.0.3 | | | | +|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | +|[greed](problems.md#greed)|0.6.1 | | |2 | +|greta |0.4.3 | | | | +|gstat |2.1-0 | | | | +|GSVA |1.46.0 | | | | +|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | +|gtfs2emis |0.1.0 | | | | +|gtfs2gps |2.1-0 | | | | +|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | +|hacksig |0.1.2 | | | | +|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | +|haldensify |0.2.3 | | | | +|hoopR |1.8.0 | | | | +|[hwep](problems.md#hwep) |2.0.0 | | |2 | +|idmodelr |0.4.0 | | | | +|imagefluency |0.2.4 | | | | +|iml |0.11.1 | | | | +|incubate |1.2.0 | | | | +|[infercnv](problems.md#infercnv)|1.14.0 | | |2 | +|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | +|[InPAS](problems.md#inpas)|2.6.0 | | |1 | +|[interflex](problems.md#interflex)|1.2.6 | | |1 | +|ipc |0.1.4 | | | | +|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | +|isopam |1.1.0 | | | | +|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | +|JointAI |1.0.4 | | | | +|jstor |0.3.10 | | | | +|JuliaConnectoR |1.1.1 | | | | +|kernelboot |0.1.9 | | | | +|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | +|latentcor |2.0.1 | | | | +|lava |1.7.1 | | | | +|ldaPrototype |0.3.1 | | | | +|ldsr |0.0.2 | | | | +|lemna |1.0.0 | | | | +|LexFindR |1.0.2 | | | | +|lgr |0.4.4 | | | | +|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | +|[lightr](problems.md#lightr)|1.7.0 | | |2 | +|lmtp |1.3.1 | | | | +|LWFBrook90R |0.5.2 | | | | +|[MAI](problems.md#mai) |1.4.0 | | |1 | +|MAMS |2.0.0 | | | | +|marginaleffects |0.9.0 | | | | +|mcmcensemble |3.0.0 | | | | +|mcp |0.3.2 | | | | +|merTools |0.5.2 | | | | +|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | +|[mice](problems.md#mice) |3.15.0 | |1 | | +|[microservices](problems.md#microservices)|0.2.0 |1 | | | +|microSTASIS |0.1.0 | | | | +|migraph |0.13.2 | | | | +|mikropml |1.5.0 | | | | +|[MineICA](problems.md#mineica)|1.38.0 |__+1__ |3 |4 | +|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | +|mistyR |1.6.0 | | | | +|mlr3 |0.14.1 | | | | +|mlr3db |0.5.0 | | | | +|mlr3pipelines |0.4.2 | | | | +|mlr3spatial |0.3.1 | | | | +|modelsummary |1.3.0 | | | | +|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | +|MOSS |0.2.2 | | | | +|mrgsim.parallel |0.2.1 | | | | +|[mslp](problems.md#mslp) |1.0.1 |1 | | | +|multiverse |0.6.1 | | | | +|netShiny |1.0 | | | | +|NetSimR |0.1.2 | | | | +|nfl4th |1.0.2 | | | | +|nflfastR |4.5.1 | | | | +|nflseedR |1.2.0 | | | | +|nncc |1.0.0 | | | | +|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | +|onemapsgapi |1.1.0 | | | | +|[OOS](problems.md#oos) |1.0.0 | | |1 | +|origami |1.0.7 | | | | +|paramsim |0.1.0 | | | | +|[partR2](problems.md#partr2)|0.9.1 | | |1 | +|[pavo](problems.md#pavo) |2.8.0 | |1 | | +|pbapply |1.7-0 | | | | +|PCRedux |1.1-2 | | | | +|PeakSegDisk |2022.2.1 | | | | +|penaltyLearning |2020.5.13 | | | | +|pGRN |0.3.5 | | | | +|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | +|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | +|PINstimation |0.1.1 | | | | +|[PLNmodels](problems.md#plnmodels)|1.0.0 | | |1 | +|plumber |1.2.1 | | | | +|polle |1.0 | | | | +|POMADE |0.1.0 | | | | +|[portvine](problems.md#portvine)|1.0.2 | | |1 | +|powRICLPM |0.1.0 | | | | +|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | +|[prewas](problems.md#prewas)|1.1.1 |__+2__ | |1 | +|progressr |0.13.0 | | | | +|[projpred](problems.md#projpred)|2.3.0 | | |1 | +|[promises](problems.md#promises)|1.2.0.1 | | |1 | +|Prostar |1.30.3 | | | | +|protti |0.6.0 | | | | +|PSCBS |0.66.0 | | | | +|PUMP |1.0.1 | | | | +|qape |2.0 | | | | +|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | +|qgcomp |2.10.1 | | | | +|qgcompint |0.7.0 | | | | +|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | +|rangeMapper |2.0.3 | | | | +|rBiasCorrection |0.3.4 | | | | +|receptiviti |0.1.3 | | | | +|refineR |1.5.1 | | | | +|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | +|remiod |1.0.2 | | | | +|[reproducible](problems.md#reproducible)|1.2.16 |1 | | | +|reval |3.1-0 | | | | +|[rgee](problems.md#rgee) |1.1.5 | | |2 | +|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | +|robust2sls |0.2.2 | | | | +|RTransferEntropy |0.2.21 | | | | +|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | +|scBubbletree |1.0.0 | | | | +|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | +|SCtools |0.3.2.1 | | | | +|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | +|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | +|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | +|seer |1.1.8 | | | | +|semtree |0.9.18 | | | | +|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[Seurat](problems.md#seurat)|4.3.0 | | |2 | +|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | +|[shiny](problems.md#shiny)|1.7.4 | | |1 | +|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | +|sigminer |2.1.9 | | | | +|Signac |1.9.0 | | | | +|[signeR](problems.md#signer)|2.0.2 | | |3 | +|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | +|simfinapi |0.2.0 | | | | +|simglm |0.8.9 | | | | +|simhelpers |0.1.2 | | | | +|sims |0.0.3 | | | | +|skewlmm |1.0.0 | | | | +|[skpr](problems.md#skpr) |1.1.6 | | |1 | +|smoots |1.1.3 | | | | +|sNPLS |1.0.27 | | | | +|[solitude](problems.md#solitude)|1.1.3 | | |1 | +|sovereign |1.2.1 | | | | +|[spaMM](problems.md#spamm)|4.1.20 | | |2 | +|[sparrpowR](problems.md#sparrpowr)|0.2.6 | |1 | | +|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | +|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | +|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | +|specr |1.0.0 | | | | +|sperrorest |3.0.5 | | | | +|spFSR |2.0.3 | | | | +|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | +|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | +|[squat](problems.md#squat)|0.1.0 | | |1 | +|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | +|[stars](problems.md#stars)|0.6-0 | | |2 | +|startR |2.2.1 | | | | +|steps |1.3.0 | | | | +|supercells |0.9.1 | | | | +|[synergyfinder](problems.md#synergyfinder)|3.6.2 | |1 |2 | +|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | +|tarchetypes |0.7.4 | | | | +|[targeted](problems.md#targeted)|0.3 | | |1 | +|targets |0.14.2 | | | | +|tcplfit2 |0.1.3 | | | | +|tealeaves |1.0.6 | | | | +|templr |0.2-0 | | | | +|[text](problems.md#text) |0.9.99.2 | | |1 | +|tglkmeans |0.3.5 | | | | +|tidyqwi |0.1.2 | | | | +|TKCat |1.0.6 | | | | +|[TreeSearch](problems.md#treesearch)|1.2.0 |1 | |1 | +|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | +|tsfeatures |1.1 | | | | +|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | +|[txshift](problems.md#txshift)|0.3.8 | | |1 | +|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.9 | | |1 | +|[updog](problems.md#updog)|2.1.3 | | |1 | +|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | +|webdeveloper |1.0.5 | | | | +|wildmeta |0.3.0 | | | | +|[wru](problems.md#wru) |1.0.1 | | |2 | +|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | +|yfR |1.0.6 | | | | diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/cran.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/cran.md index 1490c41e..cc4b3b20 100644 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/cran.md +++ b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/cran.md @@ -1,8 +1,8 @@ ## revdepcheck results -We checked 239 reverse dependencies (224 from CRAN + 15 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 276 reverse dependencies (257 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 11 new problems + * We saw 4 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -10,38 +10,17 @@ Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* alookr - checking examples ... ERROR - * blockCV checking tests ... - checking re-building of vignette outputs ... WARNING + checking re-building of vignette outputs ... ERROR * dhReg checking tests ... -* EpiNow2 - checking tests ... - -* greta - checking tests ... - -* ipc - checking re-building of vignette outputs ... WARNING - -* kernelboot +* fiery checking tests ... * prewas checking tests ... - checking re-building of vignette outputs ... WARNING - -* progressr - checking tests ... - -* rBiasCorrection - checking tests ... - -* RTransferEntropy - checking re-building of vignette outputs ... WARNING + checking re-building of vignette outputs ... ERROR diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/problems.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/problems.md index a325a908..25c71bf9 100644 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/problems.md +++ b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=multiprocess/problems.md @@ -6,7 +6,7 @@ * GitHub: https://github.com/yqzhong7/AIPW * Source code: https://github.com/cran/AIPW * Date/Publication: 2021-06-11 09:30:02 UTC -* Number of recursive dependencies: 99 +* Number of recursive dependencies: 100 Run `revdep_details(, "AIPW")` for more info @@ -22,97 +22,106 @@ Run `revdep_details(, "AIPW")` for more info All declared Imports should be used. ``` -# alookr +# AlpsNMR
-* Version: 0.3.5 -* GitHub: https://github.com/choonghyunryu/alookr -* Source code: https://github.com/cran/alookr -* Date/Publication: 2021-12-01 12:10:02 UTC -* Number of recursive dependencies: 160 +* Version: 4.0.2 +* GitHub: https://github.com/sipss/AlpsNMR +* Source code: https://github.com/cran/AlpsNMR +* Date/Publication: 2022-11-10 +* Number of recursive dependencies: 169 -Run `revdep_details(, "alookr")` for more info +Run `revdep_details(, "AlpsNMR")` for more info
-## Newly broken +## In both * checking examples ... ERROR ``` - Running examples in ‘alookr-Ex.R’ failed + Running examples in ‘AlpsNMR-Ex.R’ failed The error most likely occurred in: - > ### Name: run_models - > ### Title: Fit binary classification model - > ### Aliases: run_models + > ### Name: models_stability_plot_plsda + > ### Title: Models stability plot + > ### Aliases: models_stability_plot_plsda > > ### ** Examples > - > library(dplyr) + > # Data analysis for a table of integrated peaks ... - No variables that high unique rate. - - ── Checking character variables ─────────────────────── categorical data ── - No character variables. - - > - > # Run the model fitting. - > result <- run_models(.data = train, target = "Kyphosis", positive = "present") - Error: Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. + 18. └─vctrs::vec_default_cast(...) + 19. ├─base::withRestarts(...) + 20. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 21. │ └─base (local) doWithOneRestart(return(expr), restart) + 22. └─vctrs::stop_incompatible_cast(...) + 23. └─vctrs::stop_incompatible_type(...) + 24. └─vctrs:::stop_incompatible(...) + 25. └─vctrs:::stop_vctrs(...) + 26. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) Execution halted ``` -# AlpsNMR - -
- -* Version: 3.4.0 -* GitHub: NA -* Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 169 - -Run `revdep_details(, "AlpsNMR")` for more info - -
- -## Newly broken +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(AlpsNMR) + Loading required package: future + + Attaching package: 'AlpsNMR' + + ... + still_improving = dplyr::cumall(.data$auc_diff_above_thres), + good_ncomp = (.data$still_improving == TRUE & dplyr::lead(.data$still_improving, + default = FALSE) == FALSE))`: ℹ In argument: `good_ncomp = (...)`. + ℹ In group 2: `cv_outer_iteration = 1`, `cv_inner_iteration = 2`. + Caused by error in `vec_c()`: + ! Can't convert `..2` to . + + [ FAIL 1 | WARN 2 | SKIP 1 | PASS 90 ] + Error: Test failures + Execution halted + ``` -* checking re-building of vignette outputs ... WARNING +* checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: - ... - --- re-building ‘introduction-to-alpsnmr.Rmd’ using rmarkdown - Quitting from lines 61-63 (introduction-to-alpsnmr.Rmd) - Error: processing vignette 'introduction-to-alpsnmr.Rmd' failed with diagnostics: - Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. - --- failed re-building ‘introduction-to-alpsnmr.Rmd’ + --- re-building ‘Vig01-introduction-to-alpsnmr.Rmd’ using rmarkdown + Warning in has_utility("pdfcrop") : + pdfcrop not installed or not in PATH + sh: pdfcrop: command not found + Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : + error in running command + sh: pdfcrop: command not found + Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : + error in running command + ... + Error: processing vignette 'Vig02-handling-metadata-and-annotations.Rmd' failed with diagnostics: + cannot open the connection + --- failed re-building ‘Vig02-handling-metadata-and-annotations.Rmd’ - SUMMARY: processing the following file failed: - ‘introduction-to-alpsnmr.Rmd’ + SUMMARY: processing the following files failed: + ‘Vig01b-introduction-to-alpsnmr-old-api.Rmd’ + ‘Vig02-handling-metadata-and-annotations.Rmd’ Error: Vignette re-building failed. Execution halted ``` -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘zip’ - All declared Imports should be used. - ``` - # aroma.core
-* Version: 3.2.2 +* Version: 3.3.0 * GitHub: https://github.com/HenrikBengtsson/aroma.core * Source code: https://github.com/cran/aroma.core -* Date/Publication: 2021-01-05 05:10:12 UTC -* Number of recursive dependencies: 48 +* Date/Publication: 2022-11-15 18:30:13 UTC +* Number of recursive dependencies: 71 Run `revdep_details(, "aroma.core")` for more info @@ -130,11 +139,11 @@ Run `revdep_details(, "aroma.core")` for more info
-* Version: 2.3.3 +* Version: 2.3.4 * GitHub: https://github.com/c7rishi/BAMBI * Source code: https://github.com/cran/BAMBI -* Date/Publication: 2021-10-02 13:40:23 UTC -* Number of recursive dependencies: 49 +* Date/Publication: 2022-09-02 15:10:05 UTC +* Number of recursive dependencies: 51 Run `revdep_details(, "BAMBI")` for more info @@ -144,26 +153,20 @@ Run `revdep_details(, "BAMBI")` for more info * checking installed package size ... NOTE ``` - installed size is 6.3Mb + installed size is 7.2Mb sub-directories of 1Mb or more: - libs 5.8Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘stats4’ - All declared Imports should be used. + libs 6.7Mb ``` # baseballr
-* Version: 1.2.0 +* Version: 1.3.0 * GitHub: https://github.com/BillPetti/baseballr * Source code: https://github.com/cran/baseballr -* Date/Publication: 2022-04-25 07:20:12 UTC -* Number of recursive dependencies: 122 +* Date/Publication: 2022-09-09 07:52:55 UTC +* Number of recursive dependencies: 117 Run `revdep_details(, "baseballr")` for more info @@ -171,64 +174,66 @@ Run `revdep_details(, "baseballr")` for more info ## In both -* checking dependencies in R code ... NOTE +* checking re-building of vignette outputs ... ERROR ``` - Namespaces in Imports field not imported from: - ‘pitchRx’ ‘progressr’ - All declared Imports should be used. + Error(s) in re-building vignettes: + ... + --- re-building ‘baseballr.Rmd’ using rmarkdown + --- finished re-building ‘baseballr.Rmd’ + + --- re-building ‘ncaa_scraping.Rmd’ using rmarkdown + --- finished re-building ‘ncaa_scraping.Rmd’ + + --- re-building ‘plotting_statcast.Rmd’ using rmarkdown + --- finished re-building ‘plotting_statcast.Rmd’ + ... + Quitting from lines 38-40 (using_statcast_pitch_data.Rmd) + Error: processing vignette 'using_statcast_pitch_data.Rmd' failed with diagnostics: + HTTP error 404. + --- failed re-building ‘using_statcast_pitch_data.Rmd’ + + SUMMARY: processing the following file failed: + ‘using_statcast_pitch_data.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# BatchGetSymbols +# batchtools
-* Version: 2.6.1 -* GitHub: NA -* Source code: https://github.com/cran/BatchGetSymbols -* Date/Publication: 2020-11-28 15:10:21 UTC -* Number of recursive dependencies: 89 +* Version: 0.9.15 +* GitHub: https://github.com/mllg/batchtools +* Source code: https://github.com/cran/batchtools +* Date/Publication: 2021-01-11 12:40:03 UTC +* Number of recursive dependencies: 82 -Run `revdep_details(, "BatchGetSymbols")` for more info +Run `revdep_details(, "batchtools")` for more info
## In both -* checking LazyData ... NOTE +* checking package dependencies ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Package suggested but not available for checking: ‘doMPI’ ``` -# bcmaps - -
- -* Version: 1.0.2 -* GitHub: https://github.com/bcgov/bcmaps -* Source code: https://github.com/cran/bcmaps -* Date/Publication: 2021-03-09 23:40:03 UTC -* Number of recursive dependencies: 129 - -Run `revdep_details(, "bcmaps")` for more info - -
- -## In both - -* checking LazyData ... NOTE +* checking Rd cross-references ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Package unavailable to check Rd xrefs: ‘Rmpi’ ``` # BEKKs
-* Version: 1.1.0 +* Version: 1.4.1 * GitHub: NA * Source code: https://github.com/cran/BEKKs -* Date/Publication: 2022-03-19 00:20:02 UTC -* Number of recursive dependencies: 81 +* Date/Publication: 2022-12-18 16:40:14 UTC +* Number of recursive dependencies: 99 Run `revdep_details(, "BEKKs")` for more info @@ -238,15 +243,14 @@ Run `revdep_details(, "BEKKs")` for more info * checking installed package size ... NOTE ``` - installed size is 14.7Mb + installed size is 18.4Mb sub-directories of 1Mb or more: - libs 13.9Mb + libs 17.5Mb ``` * checking dependencies in R code ... NOTE ``` - Namespaces in Imports field not imported from: - ‘expm’ ‘forecast’ ‘parallel’ + Namespace in Imports field not imported from: ‘forecast’ All declared Imports should be used. ``` @@ -254,10 +258,10 @@ Run `revdep_details(, "BEKKs")` for more info
-* Version: 0.4.1 +* Version: 0.5.0 * GitHub: https://github.com/spatialstatisticsupna/bigDM * Source code: https://github.com/cran/bigDM -* Date/Publication: 2022-02-08 15:40:10 UTC +* Date/Publication: 2022-10-28 11:47:44 UTC * Number of recursive dependencies: 125 Run `revdep_details(, "bigDM")` for more info @@ -284,7 +288,7 @@ Run `revdep_details(, "bigDM")` for more info * GitHub: https://github.com/alexander-pastukhov/bistablehistory * Source code: https://github.com/cran/bistablehistory * Date/Publication: 2022-03-22 13:40:02 UTC -* Number of recursive dependencies: 89 +* Number of recursive dependencies: 91 Run `revdep_details(, "bistablehistory")` for more info @@ -294,9 +298,9 @@ Run `revdep_details(, "bistablehistory")` for more info * checking installed package size ... NOTE ``` - installed size is 43.3Mb + installed size is 50.3Mb sub-directories of 1Mb or more: - libs 42.4Mb + libs 49.4Mb ``` * checking dependencies in R code ... NOTE @@ -315,11 +319,11 @@ Run `revdep_details(, "bistablehistory")` for more info
-* Version: 0.4-1 +* Version: 0.4-3 * GitHub: NA * Source code: https://github.com/cran/blavaan -* Date/Publication: 2022-01-27 21:40:02 UTC -* Number of recursive dependencies: 104 +* Date/Publication: 2022-05-11 17:00:05 UTC +* Number of recursive dependencies: 98 Run `revdep_details(, "blavaan")` for more info @@ -327,12 +331,16 @@ Run `revdep_details(, "blavaan")` for more info ## In both +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘cmdstanr’ + ``` + * checking installed package size ... NOTE ``` - installed size is 71.5Mb + installed size is 87.4Mb sub-directories of 1Mb or more: - libs 68.9Mb - testdata 1.5Mb + libs 85.5Mb ``` * checking for GNU extensions in Makefiles ... NOTE @@ -348,7 +356,7 @@ Run `revdep_details(, "blavaan")` for more info * GitHub: https://github.com/rvalavi/blockCV * Source code: https://github.com/cran/blockCV * Date/Publication: 2021-06-17 04:50:02 UTC -* Number of recursive dependencies: 119 +* Number of recursive dependencies: 123 Run `revdep_details(, "blockCV")` for more info @@ -362,41 +370,33 @@ Run `revdep_details(, "blockCV")` for more info ERROR Running the tests in ‘tests/testthat.R’ failed. Last 50 lines of output: - train test - 1 167 87 - 2 87 167 [1] "SpatialBlock" The best folds was in iteration 1: train test + 1 195 59 + 2 187 67 + 3 230 24 ... - 3. │ └─base::withCallingHandlers(...) - 4. └─future::plan("multiprocess", workers = nCores) - 5. └─future plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) - 6. └─future warn_about_multiprocess(newStack) - 7. └─future warn_about_deprecated(...) - 8. └─base dfcn(msg = msg, package = .packageName) + 6. └─future:::run.Future(future) + 7. ├─base::do.call(makeFuture, args = args) + 8. └─future (local) ``(...) + 9. └─future (local) strategy(..., workers = workers, envir = envir) + 10. └─future (local) dfcn(msg = msg, package = .packageName) + 11. └─base::.Defunct(...) [ FAIL 1 | WARN 0 | SKIP 8 | PASS 193 ] Error: Test failures Execution halted ``` -* checking re-building of vignette outputs ... WARNING +* checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: ... --- re-building ‘BlockCV_for_SDM.Rmd’ using rmarkdown - Loading required package: sp - Linking to GEOS 3.9.1, GDAL 2.4.4, PROJ 4.9.3; sf_use_s2() is TRUE - Warning: `guides( = FALSE)` is deprecated. Please use `guides( = "none")` instead. - Warning: `guides( = FALSE)` is deprecated. Please use `guides( = "none")` instead. - Warning: `guides( = FALSE)` is deprecated. Please use `guides( = "none")` instead. - There are 10 raster layers - - ... Quitting from lines 205-210 (BlockCV_for_SDM.Rmd) Error: processing vignette 'BlockCV_for_SDM.Rmd' failed with diagnostics: - Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. + Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is defunct in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. --- failed re-building ‘BlockCV_for_SDM.Rmd’ SUMMARY: processing the following file failed: @@ -424,11 +424,11 @@ Run `revdep_details(, "blockCV")` for more info
-* Version: 2.17.0 +* Version: 2.18.0 * GitHub: https://github.com/paul-buerkner/brms * Source code: https://github.com/cran/brms -* Date/Publication: 2022-04-13 14:22:29 UTC -* Number of recursive dependencies: 178 +* Date/Publication: 2022-09-19 13:56:19 UTC +* Number of recursive dependencies: 175 Run `revdep_details(, "brms")` for more info @@ -443,43 +443,21 @@ Run `revdep_details(, "brms")` for more info * checking installed package size ... NOTE ``` - installed size is 8.7Mb + installed size is 7.5Mb sub-directories of 1Mb or more: - R 4.2Mb + R 3.0Mb doc 3.6Mb ``` -# cfbfastR - -
- -* Version: 1.6.4 -* GitHub: https://github.com/saiemgilani/cfbfastR -* Source code: https://github.com/cran/cfbfastR -* Date/Publication: 2021-10-27 12:30:02 UTC -* Number of recursive dependencies: 110 - -Run `revdep_details(, "cfbfastR")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘xgboost’ - All declared Imports should be used. - ``` - # ChromSCape
-* Version: 1.4.0 +* Version: 1.8.0 * GitHub: https://github.com/vallotlab/ChromSCape * Source code: https://github.com/cran/ChromSCape -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 272 +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 227 Run `revdep_details(, "ChromSCape")` for more info @@ -497,36 +475,36 @@ Run `revdep_details(, "ChromSCape")` for more info * checking installed package size ... NOTE ``` - installed size is 7.9Mb + installed size is 8.2Mb sub-directories of 1Mb or more: - data 1.3Mb + data 1.4Mb doc 2.9Mb www 2.0Mb ``` * checking R code for possible problems ... NOTE ``` - CompareWilcox: no visible binding for global variable ‘annot.’ bams_to_matrix_indexes: no visible binding for global variable ‘files_dir_list’ + enrich_TF_ChEA3_genes: no visible binding for global variable + ‘CheA3_TF_nTargets’ filter_correlated_cell_scExp: no visible binding for global variable ‘run_tsne’ generate_analysis: no visible binding for global variable ‘k’ generate_analysis: no visible binding for global variable ‘clusterConsensus’ get_most_variable_cyto: no visible binding for global variable - ‘cytoBand’ ... - plot_reduced_dim_scExp: no visible binding for global variable ‘V1’ - plot_reduced_dim_scExp: no visible binding for global variable ‘V2’ - plot_reduced_dim_scExp: no visible binding for global variable - ‘cluster’ + plot_top_TF_scExp: no visible binding for global variable ‘TF’ + rebin_matrix: no visible binding for global variable ‘new_row’ + rebin_matrix: no visible binding for global variable ‘origin_value’ subset_bam_call_peaks: no visible binding for global variable ‘merged_bam’ Undefined global functions or variables: - Fri_cyto Gain_or_Loss V1 V2 absolute_value annot. cluster - clusterConsensus cytoBand files_dir_list genes k merged_bam ncells - run_tsne sample_id total_counts + CheA3_TF_nTargets Component Fri_cyto Gain_or_Loss Gene TF V1 V2 + absolute_value cluster clusterConsensus cytoBand files_dir_list genes + group k merged_bam molecule ncells new_row orientation origin_value + percent_active run_tsne sample_id total_counts ``` * checking Rd files ... NOTE @@ -534,14 +512,6 @@ Run `revdep_details(, "ChromSCape")` for more info prepare_Rd: raw_counts_to_sparse_matrix.Rd:6-8: Dropping empty section \source ``` -* checking files in ‘vignettes’ ... NOTE - ``` - Files named as vignettes but with no recognized vignette engine: - ‘vignettes/PairedTag_Zhu_H3K4me1.Rmd’ - ‘vignettes/scChIC_Ku_H3K4me3.Rmd’ - (Is a VignetteBuilder field missing?) - ``` - # civis
@@ -600,11 +570,11 @@ Run `revdep_details(, "codebook")` for more info
-* Version: 0.4.0 +* Version: 0.5.0 * GitHub: https://github.com/M-E-Rademaker/cSEM * Source code: https://github.com/cran/cSEM -* Date/Publication: 2021-04-19 22:00:18 UTC -* Number of recursive dependencies: 122 +* Date/Publication: 2022-11-24 17:50:05 UTC +* Number of recursive dependencies: 126 Run `revdep_details(, "cSEM")` for more info @@ -626,7 +596,7 @@ Run `revdep_details(, "cSEM")` for more info * GitHub: https://github.com/adsoncostanzifilho/CSGo * Source code: https://github.com/cran/CSGo * Date/Publication: 2021-05-07 18:50:02 UTC -* Number of recursive dependencies: 74 +* Number of recursive dependencies: 76 Run `revdep_details(, "CSGo")` for more info @@ -641,79 +611,25 @@ Run `revdep_details(, "CSGo")` for more info All declared Imports should be used. ``` -# datapackage.r - -
- -* Version: 1.3.5 -* GitHub: https://github.com/frictionlessdata/datapackage-r -* Source code: https://github.com/cran/datapackage.r -* Date/Publication: 2022-01-11 10:22:47 UTC -* Number of recursive dependencies: 118 - -Run `revdep_details(, "datapackage.r")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - ── Failure (test-profile.R:106:5): profile tabular-data-package should be up-to-date ── - profile$jsonschema not equal to `response.data`. - Component "properties": Component "licenses": Component "items": Names: 2 string mismatches - Component "properties": Component "licenses": Component "items": Length mismatch: comparison on first 5 components - Component "properties": Component "licenses": Component "items": Component 4: names for target but not for current - Component "properties": Component "licenses": Component "items": Component 4: Length mismatch: comparison on first 2 components - ... - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 4: Component 1: 1 string mismatch - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 4: Component 2: Modes: list, character - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 4: Component 2: Component 1: 1 string mismatch - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 5: Names: 1 string mismatch - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 5: Length mismatch: comparison on first 2 components - ... - - [ FAIL 5 | WARN 0 | SKIP 0 | PASS 248 ] - Error: Test failures - Execution halted - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘future’ ‘iterators’ ‘readr’ - All declared Imports should be used. - ``` - -# delayed +# DeclareDesign
-* Version: 0.3.0 -* GitHub: https://github.com/tlverse/delayed -* Source code: https://github.com/cran/delayed -* Date/Publication: 2020-02-28 11:40:02 UTC -* Number of recursive dependencies: 78 +* Version: 1.0.2 +* GitHub: https://github.com/DeclareDesign/DeclareDesign +* Source code: https://github.com/cran/DeclareDesign +* Date/Publication: 2023-01-10 07:13:10 UTC +* Number of recursive dependencies: 134 -Run `revdep_details(, "delayed")` for more info +Run `revdep_details(, "DeclareDesign")` for more info
## In both -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘assertthat’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE +* checking package dependencies ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Package suggested but not available for checking: ‘DesignLibrary’ ``` # dhReg @@ -724,7 +640,7 @@ Run `revdep_details(, "delayed")` for more info * GitHub: NA * Source code: https://github.com/cran/dhReg * Date/Publication: 2021-02-28 12:30:02 UTC -* Number of recursive dependencies: 67 +* Number of recursive dependencies: 68 Run `revdep_details(, "dhReg")` for more info @@ -745,12 +661,12 @@ Run `revdep_details(, "dhReg")` for more info > # install.packages("stats") > # library(stats) ... - 1. dhReg::dhr(...) - 2. future::plan(future::multiprocess) - 3. future plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) - 4. future warn_about_multiprocess(newStack) - 5. future warn_about_deprecated(...) - 6. base dfcn(msg = msg, package = .packageName) + 4. future.apply:::future_xapply(...) + 5. future::future(...) + 7. future:::run.Future(future) + 9. future (local) ``(...) + 10. future (local) dfcn(msg = msg, package = .packageName) + 11. base::.Defunct(...) Error in reporter$stop_if_needed() : Test failed Calls: test_that -> @@ -761,11 +677,11 @@ Run `revdep_details(, "dhReg")` for more info
-* Version: 0.2.0 +* Version: 0.2.6 * GitHub: https://github.com/dipterix/dipsaus * Source code: https://github.com/cran/dipsaus -* Date/Publication: 2022-01-27 17:30:02 UTC -* Number of recursive dependencies: 76 +* Date/Publication: 2023-01-21 12:30:02 UTC +* Number of recursive dependencies: 69 Run `revdep_details(, "dipsaus")` for more info @@ -775,21 +691,62 @@ Run `revdep_details(, "dipsaus")` for more info * checking installed package size ... NOTE ``` - installed size is 5.9Mb + installed size is 5.8Mb sub-directories of 1Mb or more: - doc 1.3Mb - libs 3.5Mb + doc 1.1Mb + libs 3.3Mb + ``` + +# disk.frame + +
+ +* Version: 0.7.2 +* GitHub: https://github.com/DiskFrame/disk.frame +* Source code: https://github.com/cran/disk.frame +* Date/Publication: 2022-03-07 11:40:02 UTC +* Number of recursive dependencies: 103 + +Run `revdep_details(, "disk.frame")` for more info + +
+ +## In both + +* checking examples ... ERROR + ``` + Running examples in ‘disk.frame-Ex.R’ failed + The error most likely occurred in: + + > ### Name: anti_join.disk.frame + > ### Title: Performs join/merge for disk.frames + > ### Aliases: anti_join.disk.frame full_join.disk.frame + > ### inner_join.disk.frame left_join.disk.frame semi_join.disk.frame + > + > ### ** Examples + > + ... + Appending disk.frames: + Error in anti_join(.x, .y, by = by, copy = copy, ..., overwrite = overwrite) : + `...` must be empty. + ✖ Problematic arguments: + • ..1 = xch + • ..2 = ych + • overwrite = overwrite + ℹ Did you forget to name an argument? + Calls: anti_join ... resolve.list -> signalConditionsASAP -> signalConditions + Execution halted ``` # dispositionEffect
-* Version: 1.0.0 +* Version: 1.0.1 * GitHub: https://github.com/marcozanotti/dispositionEffect * Source code: https://github.com/cran/dispositionEffect -* Date/Publication: 2021-08-02 07:50:02 UTC -* Number of recursive dependencies: 120 +* Date/Publication: 2022-05-30 07:50:02 UTC +* Number of recursive dependencies: 135 Run `revdep_details(, "dispositionEffect")` for more info @@ -803,21 +760,21 @@ Run `revdep_details(, "dispositionEffect")` for more info ERROR Running the tests in ‘tests/testthat.R’ failed. Last 50 lines of output: - ── Failure (test-realized_duration.R:113:2): realized_duration works (realized_only = TRUE) ── + ── Failure ('test-realized_duration.R:113'): realized_duration works (realized_only = TRUE) ── realized_duration(...) not equal to c(...). 1/4 mismatches [2] 34 - 28 == 6 - ── Failure (test-realized_duration.R:116:2): realized_duration works (realized_only = TRUE) ── + ── Failure ('test-realized_duration.R:116'): realized_duration works (realized_only = TRUE) ── realized_duration(...) not equal to c(...). ... 1/4 mismatches [2] 34 - 28 == 6 - ── Failure (test-realized_duration.R:161:2): realized_duration works (realized_only = TRUE) ── + ── Failure ('test-realized_duration.R:161'): realized_duration works (realized_only = TRUE) ── realized_duration(...) not equal to c(...). 1/4 mismatches [1] 34 - 28 == 6 - [ FAIL 36 | WARN 0 | SKIP 0 | PASS 331 ] + [ FAIL 36 | WARN 1 | SKIP 0 | PASS 331 ] Error: Test failures Execution halted ``` @@ -830,7 +787,7 @@ Run `revdep_details(, "dispositionEffect")` for more info * GitHub: https://github.com/sjspielman/dragon * Source code: https://github.com/cran/dragon * Date/Publication: 2022-04-08 08:42:33 UTC -* Number of recursive dependencies: 135 +* Number of recursive dependencies: 140 Run `revdep_details(, "dragon")` for more info @@ -844,37 +801,15 @@ Run `revdep_details(, "dragon")` for more info All declared Imports should be used. ``` -# easyalluvial - -
- -* Version: 0.3.0 -* GitHub: https://github.com/erblast/easyalluvial -* Source code: https://github.com/cran/easyalluvial -* Date/Publication: 2021-01-13 10:40:09 UTC -* Number of recursive dependencies: 146 - -Run `revdep_details(, "easyalluvial")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘progress’ - All declared Imports should be used. - ``` - # EFAtools
-* Version: 0.4.1 +* Version: 0.4.4 * GitHub: https://github.com/mdsteiner/EFAtools * Source code: https://github.com/cran/EFAtools -* Date/Publication: 2022-04-24 14:40:02 UTC -* Number of recursive dependencies: 90 +* Date/Publication: 2023-01-06 14:50:40 UTC +* Number of recursive dependencies: 91 Run `revdep_details(, "EFAtools")` for more info @@ -884,9 +819,9 @@ Run `revdep_details(, "EFAtools")` for more info * checking installed package size ... NOTE ``` - installed size is 6.7Mb + installed size is 7.4Mb sub-directories of 1Mb or more: - libs 5.5Mb + libs 6.2Mb ``` * checking dependencies in R code ... NOTE @@ -899,11 +834,11 @@ Run `revdep_details(, "EFAtools")` for more info
-* Version: 0.1.13 -* GitHub: https://github.com/Waller-SUSAN/envi +* Version: 0.1.15 +* GitHub: https://github.com/lance-waller-lab/envi * Source code: https://github.com/cran/envi -* Date/Publication: 2022-03-24 08:40:17 UTC -* Number of recursive dependencies: 124 +* Date/Publication: 2022-08-30 07:00:16 UTC +* Number of recursive dependencies: 156 Run `revdep_details(, "envi")` for more info @@ -918,127 +853,113 @@ Run `revdep_details(, "envi")` for more info See ‘/c4/home/henrik/repositories/future/revdep/checks/envi/new/envi.Rcheck/00install.out’ for details. ``` -# EpiNow2 +# epitweetr
-* Version: 1.3.2 -* GitHub: https://github.com/epiforecasts/EpiNow2 -* Source code: https://github.com/cran/EpiNow2 -* Date/Publication: 2020-12-14 09:00:15 UTC -* Number of recursive dependencies: 157 +* Version: 2.2.13 +* GitHub: https://github.com/EU-ECDC/epitweetr +* Source code: https://github.com/cran/epitweetr +* Date/Publication: 2022-12-01 00:40:03 UTC +* Number of recursive dependencies: 146 -Run `revdep_details(, "EpiNow2")` for more info +Run `revdep_details(, "epitweetr")` for more info
-## Newly broken - -* checking tests ... - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(EpiNow2) - > - > test_check("EpiNow2") - [ FAIL 2 | WARN 0 | SKIP 37 | PASS 32 ] - ... - 6. └─EpiNow2::setup_future(reported_cases, strategies = "multiprocess") - 7. └─future::plan(strategies, workers = workers, gc = TRUE, earlySignal = TRUE) - 8. └─future plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) - 9. └─future warn_about_multiprocess(newStack) - 10. └─future warn_about_deprecated(...) - 11. └─base dfcn(msg = msg, package = .packageName) - - [ FAIL 2 | WARN 0 | SKIP 37 | PASS 32 ] - Error: Test failures - Execution halted - ``` - ## In both * checking package dependencies ... NOTE ``` - Package suggested but not available for checking: ‘EpiSoon’ + Package suggested but not available for checking: ‘taskscheduleR’ ``` -* checking installed package size ... NOTE +* checking dependencies in R code ... NOTE ``` - installed size is 168.1Mb - sub-directories of 1Mb or more: - libs 166.5Mb + Namespaces in Imports field not imported from: + ‘httpuv’ ‘knitr’ ‘plyr’ ‘rgdal’ ‘tidyverse’ ‘tokenizers’ ‘xml2’ + All declared Imports should be used. ``` -# epitweetr +# fect
-* Version: 2.0.3 -* GitHub: https://github.com/EU-ECDC/epitweetr -* Source code: https://github.com/cran/epitweetr -* Date/Publication: 2022-01-05 10:00:08 UTC -* Number of recursive dependencies: 143 +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/fect +* Date/Publication: 2022-10-14 09:52:32 UTC +* Number of recursive dependencies: 68 -Run `revdep_details(, "epitweetr")` for more info +Run `revdep_details(, "fect")` for more info
## In both -* checking package dependencies ... NOTE +* checking installed package size ... NOTE ``` - Package suggested but not available for checking: ‘taskscheduleR’ - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.1Mb + installed size is 13.9Mb sub-directories of 1Mb or more: - doc 3.0Mb - java 1.3Mb + libs 12.7Mb ``` * checking dependencies in R code ... NOTE ``` - Namespaces in Imports field not imported from: - ‘httpuv’ ‘knitr’ ‘plyr’ ‘tidyverse’ ‘tokenizers’ ‘xml2’ + Namespace in Imports field not imported from: ‘panelView’ All declared Imports should be used. ``` -# fipe +# fiery
-* Version: 0.0.1 -* GitHub: https://github.com/italocegatta/fipe -* Source code: https://github.com/cran/fipe -* Date/Publication: 2019-08-25 07:20:06 UTC -* Number of recursive dependencies: 66 +* Version: 1.1.4 +* GitHub: https://github.com/thomasp85/fiery +* Source code: https://github.com/cran/fiery +* Date/Publication: 2022-08-16 07:20:06 UTC +* Number of recursive dependencies: 74 -Run `revdep_details(, "fipe")` for more info +Run `revdep_details(, "fiery")` for more info
-## In both +## Newly broken -* checking LazyData ... NOTE +* checking tests ... ``` - 'LazyData' is specified without a 'data' directory + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(fiery) + > + > test_check("fiery") + + [ FAIL 1 | WARN 0 | SKIP 1 | PASS 253 ] + ... + 2. └─private$ASYNC$add(substitute(expr), then, substituted = TRUE) + 3. └─private$make_future(expr, then, ...) + 4. ├─base::do.call(private$catcher, list(expr = expr, lazy = private$lazy)) + 5. └─future::multiprocess(...) + 6. └─future (local) dfcn(msg = msg, package = .packageName) + 7. └─base::.Defunct(...) + + [ FAIL 1 | WARN 0 | SKIP 1 | PASS 253 ] + Error: Test failures + Execution halted ``` # flowGraph
-* Version: 1.2.0 +* Version: 1.6.0 * GitHub: https://github.com/aya49/flowGraph * Source code: https://github.com/cran/flowGraph -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 87 +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 92 Run `revdep_details(, "flowGraph")` for more info @@ -1046,31 +967,6 @@ Run `revdep_details(, "flowGraph")` for more info ## In both -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘flowGraph.Rmd’ using rmarkdown - - 8 pops @ layer 1 - 23:56:06-23:56:06 > 16:00:00 - - 24 pops @ layer 2 - 23:56:06-23:56:06 > 16:00:00 - - 32 pops @ layer 3 - 23:56:06-23:56:06 > 16:00:00 - - 16 pops @ layer 4 - 23:56:06-23:56:06 > 16:00:00 - ... - Quitting from lines 557-561 (flowGraph.Rmd) - Error: processing vignette 'flowGraph.Rmd' failed with diagnostics: - `map_df()` requires dplyr - --- failed re-building ‘flowGraph.Rmd’ - - SUMMARY: processing the following file failed: - ‘flowGraph.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - * checking R code for possible problems ... NOTE ``` get_child: no visible binding for global variable ‘no_cores’ @@ -1093,7 +989,7 @@ Run `revdep_details(, "flowGraph")` for more info * GitHub: https://github.com/ianjonsen/foieGras * Source code: https://github.com/cran/foieGras * Date/Publication: 2021-04-26 22:10:07 UTC -* Number of recursive dependencies: 139 +* Number of recursive dependencies: 140 Run `revdep_details(, "foieGras")` for more info @@ -1103,9 +999,9 @@ Run `revdep_details(, "foieGras")` for more info * checking installed package size ... NOTE ``` - installed size is 40.9Mb + installed size is 49.9Mb sub-directories of 1Mb or more: - libs 40.0Mb + libs 49.0Mb ``` # forecastML @@ -1116,7 +1012,7 @@ Run `revdep_details(, "foieGras")` for more info * GitHub: https://github.com/nredell/forecastML * Source code: https://github.com/cran/forecastML * Date/Publication: 2020-05-07 15:10:17 UTC -* Number of recursive dependencies: 100 +* Number of recursive dependencies: 102 Run `revdep_details(, "forecastML")` for more info @@ -1134,11 +1030,11 @@ Run `revdep_details(, "forecastML")` for more info
-* Version: 0.2.0 +* Version: 0.3.2 * GitHub: https://github.com/JeremyGelb/geocmeans * Source code: https://github.com/cran/geocmeans -* Date/Publication: 2021-08-23 07:11:35 UTC -* Number of recursive dependencies: 204 +* Date/Publication: 2023-01-08 21:40:02 UTC +* Number of recursive dependencies: 197 Run `revdep_details(, "geocmeans")` for more info @@ -1148,45 +1044,11 @@ Run `revdep_details(, "geocmeans")` for more info * checking installed package size ... NOTE ``` - installed size is 11.4Mb + installed size is 14.3Mb sub-directories of 1Mb or more: - data 2.3Mb - doc 1.9Mb - libs 6.1Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘rgdal’ - All declared Imports should be used. - ``` - -# GetBCBData - -
- -* Version: 0.6 -* GitHub: https://github.com/msperlin/GetBCBData -* Source code: https://github.com/cran/GetBCBData -* Date/Publication: 2021-01-21 17:40:07 UTC -* Number of recursive dependencies: 88 - -Run `revdep_details(, "GetBCBData")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘RCurl’ ‘lubridate’ ‘readr’ ‘stats’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory + doc 1.7Mb + extdata 3.0Mb + libs 8.0Mb ``` # googleComputeEngineR @@ -1233,44 +1095,15 @@ Run `revdep_details(, "googleTagManageR")` for more info All declared Imports should be used. ``` -# grattan - -
- -* Version: 1.9.0.10 -* GitHub: https://github.com/HughParsonage/grattan -* Source code: https://github.com/cran/grattan -* Date/Publication: 2022-01-10 01:02:41 UTC -* Number of recursive dependencies: 121 - -Run `revdep_details(, "grattan")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Packages suggested but not available for checking: - 'taxstats', 'taxstats1516' - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.1Mb - sub-directories of 1Mb or more: - libs 4.1Mb - ``` - # greed
-* Version: 0.6.0 +* Version: 0.6.1 * GitHub: https://github.com/comeetie/greed * Source code: https://github.com/cran/greed -* Date/Publication: 2022-03-18 12:50:02 UTC -* Number of recursive dependencies: 93 +* Date/Publication: 2022-10-03 22:00:05 UTC +* Number of recursive dependencies: 96 Run `revdep_details(, "greed")` for more info @@ -1280,9 +1113,9 @@ Run `revdep_details(, "greed")` for more info * checking installed package size ... NOTE ``` - installed size is 28.3Mb + installed size is 36.8Mb sub-directories of 1Mb or more: - libs 26.0Mb + libs 34.6Mb ``` * checking data for non-ASCII characters ... NOTE @@ -1290,45 +1123,27 @@ Run `revdep_details(, "greed")` for more info Note: found 989 marked UTF-8 strings ``` -# greta +# gsynth
-* Version: 0.4.2 -* GitHub: https://github.com/greta-dev/greta -* Source code: https://github.com/cran/greta -* Date/Publication: 2022-03-22 13:00:02 UTC -* Number of recursive dependencies: 167 +* Version: 1.2.1 +* GitHub: NA +* Source code: https://github.com/cran/gsynth +* Date/Publication: 2021-08-06 07:50:05 UTC +* Number of recursive dependencies: 65 -Run `revdep_details(, "greta")` for more info +Run `revdep_details(, "gsynth")` for more info
-## Newly broken +## In both -* checking tests ... +* checking installed package size ... NOTE ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - - i Initialising python and checking dependencies, this may take a moment. - x Initialising python and checking dependencies, this may take a moment. ... ... - - i Initialising python and checking dependencies, this may take a moment. - ... - 4. └─future plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) - 5. └─future warn_about_multiprocess(newStack) - 6. └─future warn_about_deprecated(...) - 7. └─base dfcn(msg = msg, package = .packageName) - - [ FAIL 1 | WARN 0 | SKIP 250 | PASS 5 ] - Deleting unused snapshots: - • greta-sitrep.md - Error: Test failures - Execution halted + installed size is 5.2Mb + sub-directories of 1Mb or more: + libs 4.9Mb ``` # gWQS @@ -1339,7 +1154,7 @@ Run `revdep_details(, "greta")` for more info * GitHub: NA * Source code: https://github.com/cran/gWQS * Date/Publication: 2021-05-20 09:30:02 UTC -* Number of recursive dependencies: 102 +* Number of recursive dependencies: 103 Run `revdep_details(, "gWQS")` for more info @@ -1361,7 +1176,7 @@ Run `revdep_details(, "gWQS")` for more info * GitHub: https://github.com/szymanskir/hackeRnews * Source code: https://github.com/cran/hackeRnews * Date/Publication: 2019-12-13 13:20:05 UTC -* Number of recursive dependencies: 68 +* Number of recursive dependencies: 69 Run `revdep_details(, "hackeRnews")` for more info @@ -1382,7 +1197,7 @@ Run `revdep_details(, "hackeRnews")` for more info * GitHub: https://github.com/tlverse/hal9001 * Source code: https://github.com/cran/hal9001 * Date/Publication: 2022-02-09 22:50:02 UTC -* Number of recursive dependencies: 96 +* Number of recursive dependencies: 98 Run `revdep_details(, "hal9001")` for more info @@ -1392,20 +1207,20 @@ Run `revdep_details(, "hal9001")` for more info * checking installed package size ... NOTE ``` - installed size is 6.1Mb + installed size is 7.6Mb sub-directories of 1Mb or more: - libs 5.7Mb + libs 7.2Mb ``` # hwep
-* Version: 0.0.1 -* GitHub: NA +* Version: 2.0.0 +* GitHub: https://github.com/dcgerard/hwep * Source code: https://github.com/cran/hwep -* Date/Publication: 2021-09-28 10:30:02 UTC -* Number of recursive dependencies: 69 +* Date/Publication: 2022-08-16 07:20:02 UTC +* Number of recursive dependencies: 110 Run `revdep_details(, "hwep")` for more info @@ -1413,43 +1228,27 @@ Run `revdep_details(, "hwep")` for more info ## In both -* checking dependencies in R code ... NOTE +* checking installed package size ... NOTE ``` - Namespace in Imports field not imported from: ‘future’ - All declared Imports should be used. + installed size is 68.6Mb + sub-directories of 1Mb or more: + libs 68.1Mb ``` -# iml - -
- -* Version: 0.10.1 -* GitHub: https://github.com/christophM/iml -* Source code: https://github.com/cran/iml -* Date/Publication: 2020-09-24 12:30:14 UTC -* Number of recursive dependencies: 168 - -Run `revdep_details(, "iml")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE +* checking for GNU extensions in Makefiles ... NOTE ``` - Namespace in Imports field not imported from: ‘keras’ - All declared Imports should be used. + GNU make is a SystemRequirements. ``` # infercnv
-* Version: 1.10.1 +* Version: 1.14.0 * GitHub: https://github.com/broadinstitute/inferCNV * Source code: https://github.com/cran/infercnv -* Date/Publication: 2021-11-08 -* Number of recursive dependencies: 135 +* Date/Publication: 2022-11-02 +* Number of recursive dependencies: 196 Run `revdep_details(, "infercnv")` for more info @@ -1459,7 +1258,7 @@ Run `revdep_details(, "infercnv")` for more info * checking installed package size ... NOTE ``` - installed size is 5.0Mb + installed size is 5.1Mb sub-directories of 1Mb or more: extdata 3.1Mb ``` @@ -1491,168 +1290,223 @@ Run `revdep_details(, "inlinedocs")` for more info Package unavailable to check Rd xrefs: ‘R.methodsS3’ ``` -# ipc +# InPAS
-* Version: 0.1.3 -* GitHub: https://github.com/fellstat/ipc -* Source code: https://github.com/cran/ipc -* Date/Publication: 2019-06-23 06:00:03 UTC -* Number of recursive dependencies: 69 +* Version: 2.6.0 +* GitHub: NA +* Source code: https://github.com/cran/InPAS +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 166 -Run `revdep_details(, "ipc")` for more info +Run `revdep_details(, "InPAS")` for more info
-## Newly broken - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘shinymp.Rmd’ using rmarkdown - Quitting from lines 21-43 (shinymp.Rmd) - Error: processing vignette 'shinymp.Rmd' failed with diagnostics: - Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. - --- failed re-building ‘shinymp.Rmd’ - - SUMMARY: processing the following file failed: - ‘shinymp.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - ## In both -* checking LazyData ... NOTE +* checking dependencies in R code ... NOTE ``` - 'LazyData' is specified without a 'data' directory + There are ::: calls to the package's namespace in its code. A package + almost never needs to use ::: for its own objects: + ‘adjust_distalCPs’ ‘adjust_proximalCPs’ ‘adjust_proximalCPsByNBC’ + ‘adjust_proximalCPsByPWM’ ‘calculate_mse’ ‘find_valleyBySpline’ + ‘get_PAscore’ ‘get_PAscore2’ ‘remove_convergentUTR3s’ + ‘search_distalCPs’ ‘search_proximalCPs’ ``` -# ivmte +# interflex
-* Version: 1.4.0 +* Version: 1.2.6 * GitHub: NA -* Source code: https://github.com/cran/ivmte -* Date/Publication: 2021-09-17 12:20:07 UTC -* Number of recursive dependencies: 111 +* Source code: https://github.com/cran/interflex +* Date/Publication: 2021-05-18 11:40:02 UTC +* Number of recursive dependencies: 99 -Run `revdep_details(, "ivmte")` for more info +Run `revdep_details(, "interflex")` for more info
## In both -* checking package dependencies ... NOTE +* checking installed package size ... NOTE ``` - Packages suggested but not available for checking: 'gurobi', 'cplexAPI' + installed size is 5.8Mb + sub-directories of 1Mb or more: + libs 5.1Mb ``` -# kernelboot +# ISAnalytics
-* Version: 0.1.7 -* GitHub: https://github.com/twolodzko/kernelboot -* Source code: https://github.com/cran/kernelboot -* Date/Publication: 2020-02-13 23:10:03 UTC -* Number of recursive dependencies: 64 +* Version: 1.8.1 +* GitHub: https://github.com/calabrialab/ISAnalytics +* Source code: https://github.com/cran/ISAnalytics +* Date/Publication: 2022-12-01 +* Number of recursive dependencies: 171 -Run `revdep_details(, "kernelboot")` for more info +Run `revdep_details(, "ISAnalytics")` for more info
-## Newly broken +## In both + +* checking examples ... ERROR + ``` + Running examples in ‘ISAnalytics-Ex.R’ failed + The error most likely occurred in: + + > ### Name: import_Vispa2_stats + > ### Title: Import Vispa2 stats given the aligned association file. + > ### Aliases: import_Vispa2_stats + > + > ### ** Examples + > + > fs_path <- generate_default_folder_structure(type = "correct") + ... + 2. │ ├─ISAnalytics:::.manage_association_file(...) + 3. │ │ └─ISAnalytics:::.check_file_system_alignment(...) + 4. │ │ └─proj_fold_col %in% colnames(df) + 5. │ └─dplyr::if_else(...) + 6. │ └─dplyr:::vec_case_when(...) + 7. │ └─vctrs::list_check_all_vectors(values, arg = values_arg, call = call) + 8. └─vctrs:::stop_scalar_type(``(NULL), "false", ``) + 9. └─vctrs:::stop_vctrs(...) + 10. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + Execution halted + ``` * checking tests ... ``` - Running ‘test_parallel.R’ + Running ‘testthat.R’ ERROR - Running the tests in ‘tests/test_parallel.R’ failed. + Running the tests in ‘tests/testthat.R’ failed. Complete output: - > - > library("kernelboot") - > - > if ( future::availableCores() > 1L ) { - + - + # simply check if it fails + > library(testthat) + > library(ISAnalytics) + Loading required package: magrittr + + Attaching package: 'magrittr' + ... - + - + set.seed(0xBEEF) - + s2 <- kernelboot(mtcars, function(data) coef(lm(mpg ~ disp + hp + drat, data = data)), - + R = 10, parallel = TRUE, workers = 2L) - + - + stopifnot( all.equal(s1, s2) ) - + - + } - Error: Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. + 13. │ ├─ISAnalytics:::.manage_association_file(...) + 14. │ │ └─ISAnalytics:::.check_file_system_alignment(...) + 15. │ │ └─proj_fold_col %in% colnames(df) + 16. │ └─dplyr::if_else(...) + 17. │ └─dplyr:::vec_case_when(...) + 18. │ └─vctrs::list_check_all_vectors(values, arg = values_arg, call = call) + 19. └─vctrs:::stop_scalar_type(``(NULL), "false", ``) + 20. └─vctrs:::stop_vctrs(...) + 21. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) Execution halted ``` -## In both +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘ISAnalytics.Rmd’ using rmarkdown + --- finished re-building ‘ISAnalytics.Rmd’ + + --- re-building ‘sharing_analyses.Rmd’ using rmarkdown + --- finished re-building ‘sharing_analyses.Rmd’ + + --- re-building ‘workflow_start.Rmd’ using rmarkdown + Quitting from lines 466-470 (workflow_start.Rmd) + Error: processing vignette 'workflow_start.Rmd' failed with diagnostics: + `false` must be a vector, not `NULL`. + --- failed re-building ‘workflow_start.Rmd’ + + SUMMARY: processing the following file failed: + ‘workflow_start.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 7.9Mb + sub-directories of 1Mb or more: + data 1.4Mb + doc 4.4Mb ``` -# keyATM +* checking R code for possible problems ... NOTE + ``` + .sh_row_permut: no visible global function definition for ‘.’ + .sharing_multdf_mult_key: no visible binding for global variable ‘.’ + .sharing_multdf_single_key: no visible binding for global variable ‘.’ + .sharing_singledf_mult_key: no visible binding for global variable ‘.’ + .sharing_singledf_single_key: no visible binding for global variable + ‘.’ + cumulative_is: no visible binding for global variable ‘is’ + gene_frequency_fisher: no visible binding for global variable ‘.’ + Undefined global functions or variables: + . is + Consider adding + importFrom("methods", "is") + to your NAMESPACE file (and ensure that your DESCRIPTION Imports field + contains 'methods'). + ``` + +# ivmte
-* Version: 0.4.0 -* GitHub: https://github.com/keyATM/keyATM -* Source code: https://github.com/cran/keyATM -* Date/Publication: 2021-02-14 17:40:02 UTC -* Number of recursive dependencies: 107 +* Version: 1.4.0 +* GitHub: NA +* Source code: https://github.com/cran/ivmte +* Date/Publication: 2021-09-17 12:20:07 UTC +* Number of recursive dependencies: 110 -Run `revdep_details(, "keyATM")` for more info +Run `revdep_details(, "ivmte")` for more info
## In both -* checking installed package size ... NOTE +* checking package dependencies ... NOTE ``` - installed size is 18.9Mb - sub-directories of 1Mb or more: - libs 18.5Mb + Packages suggested but not available for checking: 'gurobi', 'cplexAPI' ``` -# lava +# keyATM
-* Version: 1.6.10 -* GitHub: https://github.com/kkholst/lava -* Source code: https://github.com/cran/lava -* Date/Publication: 2021-09-02 14:50:18 UTC -* Number of recursive dependencies: 131 +* Version: 0.4.2 +* GitHub: https://github.com/keyATM/keyATM +* Source code: https://github.com/cran/keyATM +* Date/Publication: 2023-01-06 18:50:52 UTC +* Number of recursive dependencies: 107 -Run `revdep_details(, "lava")` for more info +Run `revdep_details(, "keyATM")` for more info
## In both -* checking package dependencies ... NOTE +* checking installed package size ... NOTE ``` - Packages suggested but not available for checking: 'gof', 'lava.tobit' + installed size is 23.9Mb + sub-directories of 1Mb or more: + libs 23.6Mb ``` # lidR
-* Version: 4.0.0 +* Version: 4.0.2 * GitHub: https://github.com/r-lidar/lidR * Source code: https://github.com/cran/lidR -* Date/Publication: 2022-02-18 16:10:03 UTC -* Number of recursive dependencies: 158 +* Date/Publication: 2022-12-15 15:10:02 UTC +* Number of recursive dependencies: 157 Run `revdep_details(, "lidR")` for more info @@ -1665,20 +1519,20 @@ Run `revdep_details(, "lidR")` for more info Running examples in ‘lidR-Ex.R’ failed The error most likely occurred in: - > ### Name: its_dalponte2016 + > ### Name: its_silva2016 > ### Title: Individual Tree Segmentation Algorithm - > ### Aliases: its_dalponte2016 dalponte2016 + > ### Aliases: its_silva2016 silva2016 > > ### ** Examples > > LASfile <- system.file("extdata", "MixedConifer.laz", package="lidR") ... - > chm <- rasterize_canopy(las, 0.5, p2r(0.3), pkg = "raster") + > chm <- rasterize_canopy(las, res = 0.5, p2r(0.3), pkg = "raster") > ker <- matrix(1,3,3) > chm <- raster::focal(chm, w = ker, fun = mean, na.rm = TRUE) > > ttops <- locate_trees(chm, lmf(4, 2)) - > las <- segment_trees(las, dalponte2016(chm, ttops)) + > las <- segment_trees(las, silva2016(chm, ttops)) Error in geos_op2_geom("intersection", x, y, ...) : st_crs(x) == st_crs(y) is not TRUE Calls: segment_trees ... st_intersection.sf -> geos_op2_df -> geos_op2_geom -> stopifnot @@ -1687,93 +1541,136 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’ + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 211249 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + ERROR Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - 3. └─lidR algorithm(st_bbox(las)) - 4. └─lidR:::crop_special_its(treetops, chm, bbox) - 5. └─lidR:::raster_crop(chm, bbox) - 6. ├─sf::st_crop(raster, bbox) - 7. └─stars:::st_crop.stars(raster, bbox) - ── Error (test-segment_trees.R:147:3): Silva algorithm works with sfc ────────── - ... - 7. └─lidR:::segment_trees.LAS(las, silva2016(chm, ttops_shifted500)) - 8. └─lidR algorithm(st_bbox(las)) - 9. └─lidR:::crop_special_its(treetops, chm, bbox) - 10. └─lidR:::raster_crop(chm, bbox) - 11. ├─sf::st_crop(raster, bbox) - 12. └─stars:::st_crop.stars(raster, bbox) - - [ FAIL 20 | WARN 5 | SKIP 40 | PASS 1345 ] - Error: Test failures - Execution halted + Complete output: + > Sys.setenv("R_TESTS" = "") + > + > library(testthat) + > library(lidR) + > test_check("lidR") + Tests using raster: terra + Tests using future: TRUE + Tests using OpenMP thread: 32 + OGR: Unsupported geometry type + OGR: Unsupported geometry type + terminate called after throwing an instance of 'std::length_error' + what(): basic_string::_S_create ``` * checking installed package size ... NOTE ``` - installed size is 15.8Mb + installed size is 19.7Mb sub-directories of 1Mb or more: - R 1.1Mb - doc 1.0Mb + R 1.2Mb extdata 1.1Mb - libs 12.0Mb + libs 15.8Mb + ``` + +# lightr + +
+ +* Version: 1.7.0 +* GitHub: https://github.com/ropensci/lightr +* Source code: https://github.com/cran/lightr +* Date/Publication: 2022-05-14 13:50:02 UTC +* Number of recursive dependencies: 77 + +Run `revdep_details(, "lightr")` for more info + +
+ +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘pavo’ + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘pavo’ + ``` + +# MAI + +
+ +* Version: 1.4.0 +* GitHub: https://github.com/KechrisLab/MAI +* Source code: https://github.com/cran/MAI +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 168 + +Run `revdep_details(, "MAI")` for more info + +
+ +## In both + +* checking top-level files ... NOTE + ``` + File + LICENSE + is not mentioned in the DESCRIPTION file. ``` -# lmtp +# metabolomicsR
* Version: 1.0.0 -* GitHub: https://github.com/nt-williams/lmtp -* Source code: https://github.com/cran/lmtp -* Date/Publication: 2021-09-29 07:10:07 UTC -* Number of recursive dependencies: 113 +* GitHub: https://github.com/XikunHan/metabolomicsR +* Source code: https://github.com/cran/metabolomicsR +* Date/Publication: 2022-04-29 07:40:02 UTC +* Number of recursive dependencies: 163 -Run `revdep_details(, "lmtp")` for more info +Run `revdep_details(, "metabolomicsR")` for more info
## In both -* checking dependencies in R code ... NOTE +* checking package dependencies ... NOTE ``` - Namespaces in Imports field not imported from: - ‘R6’ ‘nnls’ ‘utils’ - All declared Imports should be used. + Package suggested but not available for checking: ‘genuMet’ ``` -# MAI +# mice
-* Version: 1.0.0 -* GitHub: https://github.com/KechrisLab/MAI -* Source code: https://github.com/cran/MAI -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 164 +* Version: 3.15.0 +* GitHub: https://github.com/amices/mice +* Source code: https://github.com/cran/mice +* Date/Publication: 2022-11-19 13:00:02 UTC +* Number of recursive dependencies: 133 -Run `revdep_details(, "MAI")` for more info +Run `revdep_details(, "mice")` for more info
## In both -* checking top-level files ... NOTE +* checking Rd cross-references ... WARNING ``` - File - LICENSE - is not mentioned in the DESCRIPTION file. + Missing link or links in documentation object 'mice.impute.cart.Rd': + ‘rpart.control’ + + See section 'Cross-references' in the 'Writing R Extensions' manual. ``` # microservices
-* Version: 0.1.2 +* Version: 0.2.0 * GitHub: https://github.com/tidylab/microservices * Source code: https://github.com/cran/microservices -* Date/Publication: 2021-06-12 06:10:02 UTC +* Date/Publication: 2022-10-01 09:50:02 UTC * Number of recursive dependencies: 69 Run `revdep_details(, "microservices")` for more info @@ -1807,22 +1704,15 @@ Run `revdep_details(, "microservices")` for more info Execution halted ``` -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘config’ ‘desc’ ‘dplyr’ ‘glue’ ‘withr’ - All declared Imports should be used. - ``` - # MineICA
-* Version: 1.34.0 +* Version: 1.38.0 * GitHub: NA * Source code: https://github.com/cran/MineICA -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 208 +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 217 Run `revdep_details(, "MineICA")` for more info @@ -1851,12 +1741,32 @@ Run `revdep_details(, "MineICA")` for more info Warning: executing %dopar% sequentially: no parallel backend registered FastICA iteration 2 FastICA iteration 3 - Error: Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. + Error: Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is defunct in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Execution halted ``` ## In both +* checking dependencies in R code ... WARNING + ``` + Namespace in Imports field not imported from: ‘lumiHumanAll.db’ + All declared Imports should be used. + Packages in Depends field not imported from: + ‘GOstats’ ‘Hmisc’ ‘JADE’ ‘RColorBrewer’ ‘Rgraphviz’ ‘annotate’ + ‘biomaRt’ ‘cluster’ ‘colorspace’ ‘fastICA’ ‘foreach’ ‘ggplot2’ + ‘graph’ ‘gtools’ ‘igraph’ ‘marray’ ‘mclust’ ‘methods’ ‘plyr’ ‘scales’ + ‘xtable’ + These packages need to be imported from (in the NAMESPACE file) + for when this namespace is loaded but not attached. + Missing or unexported object: ‘GOstats::geneIdsByCategory’ + ':::' calls which should be '::': + ‘Biobase:::annotation<-’ ‘Biobase:::validMsg’ ‘fpc:::pamk’ + ‘lumi:::getChipInfo’ ‘mclust:::adjustedRandIndex’ + See the note in ?`:::` about the use of this operator. + Unexported object imported by a ':::' call: ‘Biobase:::isValidVersion’ + See the note in ?`:::` about the use of this operator. + ``` + * checking Rd cross-references ... WARNING ``` Missing link or links in documentation object 'Alist.Rd': @@ -1907,39 +1817,18 @@ Run `revdep_details(, "MineICA")` for more info A package should be listed in only one of these fields. ``` -* checking dependencies in R code ... NOTE - ``` - 'library' or 'require' call to ‘GOstats’ which was already attached by Depends. - Please remove these calls from your code. - Namespace in Imports field not imported from: ‘lumiHumanAll.db’ - All declared Imports should be used. - Packages in Depends field not imported from: - ‘GOstats’ ‘Hmisc’ ‘JADE’ ‘RColorBrewer’ ‘Rgraphviz’ ‘annotate’ - ‘biomaRt’ ‘cluster’ ‘colorspace’ ‘fastICA’ ‘foreach’ ‘ggplot2’ - ‘graph’ ‘gtools’ ‘igraph’ ‘marray’ ‘mclust’ ‘methods’ ‘plyr’ ‘scales’ - ‘xtable’ - These packages need to be imported from (in the NAMESPACE file) - for when this namespace is loaded but not attached. - ':::' calls which should be '::': - ‘Biobase:::annotation<-’ ‘Biobase:::validMsg’ ‘fpc:::pamk’ - ‘lumi:::getChipInfo’ ‘mclust:::adjustedRandIndex’ - See the note in ?`:::` about the use of this operator. - Unexported object imported by a ':::' call: ‘Biobase:::isValidVersion’ - See the note in ?`:::` about the use of this operator. - ``` - * checking R code for possible problems ... NOTE ``` - addGenesToGoReport: no visible global function definition for - ‘geneIdsByCategory’ - addGenesToGoReport: no visible global function definition for - ‘geneIdUniverse’ addGenesToGoReport: no visible global function definition for ‘conditional’ addGenesToGoReport: no visible global function definition for ‘sigCategories’ annot2Color: no visible global function definition for ‘brewer.pal’ annot2Color: no visible global function definition for ‘heat_hcl’ + annot2Color: no visible global function definition for ‘terrain_hcl’ + annot2Color: no visible global function definition for ‘cm.colors’ + annot2Color: no visible global function definition for ‘rainbow_hcl’ + annotFeatures: no visible global function definition for ‘na.omit’ ... importFrom("methods", "callNextMethod", "new", "validObject") importFrom("stats", "aggregate", "as.dendrogram", "as.dist", @@ -1982,11 +1871,11 @@ Run `revdep_details(, "MineICA")` for more info
-* Version: 1.0.2 +* Version: 1.0.3 * GitHub: https://github.com/grossSBM/missSBM * Source code: https://github.com/cran/missSBM -* Date/Publication: 2022-02-01 16:00:20 UTC -* Number of recursive dependencies: 108 +* Date/Publication: 2022-08-23 12:10:06 UTC +* Number of recursive dependencies: 109 Run `revdep_details(, "missSBM")` for more info @@ -1996,20 +1885,20 @@ Run `revdep_details(, "missSBM")` for more info * checking installed package size ... NOTE ``` - installed size is 8.4Mb + installed size is 9.7Mb sub-directories of 1Mb or more: - libs 6.5Mb + libs 7.8Mb ``` # momentuHMM
-* Version: 1.5.4 +* Version: 1.5.5 * GitHub: https://github.com/bmcclintock/momentuHMM * Source code: https://github.com/cran/momentuHMM -* Date/Publication: 2021-09-03 04:30:02 UTC -* Number of recursive dependencies: 195 +* Date/Publication: 2022-10-18 20:52:35 UTC +* Number of recursive dependencies: 142 Run `revdep_details(, "momentuHMM")` for more info @@ -2019,32 +1908,72 @@ Run `revdep_details(, "momentuHMM")` for more info * checking installed package size ... NOTE ``` - installed size is 9.1Mb + installed size is 10.1Mb sub-directories of 1Mb or more: R 1.2Mb doc 1.7Mb - libs 5.6Mb + libs 6.6Mb ``` -# onemapsgapi +# mslp
-* Version: 1.0.0 +* Version: 1.0.1 * GitHub: NA -* Source code: https://github.com/cran/onemapsgapi -* Date/Publication: 2020-02-06 11:00:02 UTC -* Number of recursive dependencies: 66 +* Source code: https://github.com/cran/mslp +* Date/Publication: 2022-11-20 +* Number of recursive dependencies: 88 -Run `revdep_details(, "onemapsgapi")` for more info +Run `revdep_details(, "mslp")` for more info
## In both -* checking LazyData ... NOTE +* checking re-building of vignette outputs ... ERROR ``` - 'LazyData' is specified without a 'data' directory + Error(s) in re-building vignettes: + ... + --- re-building ‘mslp.Rmd’ using rmarkdown + Error: processing vignette 'mslp.Rmd' failed with diagnostics: + there is no package called ‘BiocStyle’ + --- failed re-building ‘mslp.Rmd’ + + SUMMARY: processing the following file failed: + ‘mslp.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# oncomsm + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/Boehringer-Ingelheim/oncomsm +* Source code: https://github.com/cran/oncomsm +* Date/Publication: 2022-12-09 14:40:09 UTC +* Number of recursive dependencies: 122 + +Run `revdep_details(, "oncomsm")` for more info + +
+ +## In both + +* checking installed package size ... NOTE + ``` + installed size is 55.3Mb + sub-directories of 1Mb or more: + doc 1.3Mb + libs 53.0Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. ``` # OOS @@ -2055,7 +1984,7 @@ Run `revdep_details(, "onemapsgapi")` for more info * GitHub: https://github.com/tylerJPike/OOS * Source code: https://github.com/cran/OOS * Date/Publication: 2021-03-17 13:20:20 UTC -* Number of recursive dependencies: 131 +* Number of recursive dependencies: 134 Run `revdep_details(, "OOS")` for more info @@ -2076,7 +2005,7 @@ Run `revdep_details(, "OOS")` for more info * GitHub: https://github.com/mastoffel/partR2 * Source code: https://github.com/cran/partR2 * Date/Publication: 2021-01-18 16:30:04 UTC -* Number of recursive dependencies: 91 +* Number of recursive dependencies: 92 Run `revdep_details(, "partR2")` for more info @@ -2094,11 +2023,11 @@ Run `revdep_details(, "partR2")` for more info
-* Version: 2.7.1 +* Version: 2.8.0 * GitHub: https://github.com/rmaia/pavo * Source code: https://github.com/cran/pavo -* Date/Publication: 2021-09-21 13:10:21 UTC -* Number of recursive dependencies: 87 +* Date/Publication: 2022-08-16 13:00:20 UTC +* Number of recursive dependencies: 92 Run `revdep_details(, "pavo")` for more info @@ -2117,11 +2046,11 @@ Run `revdep_details(, "pavo")` for more info
-* Version: 2.0.1 +* Version: 2.1.1 * GitHub: https://github.com/cdmuir/photosynthesis * Source code: https://github.com/cran/photosynthesis -* Date/Publication: 2021-07-01 04:30:02 UTC -* Number of recursive dependencies: 104 +* Date/Publication: 2022-11-19 19:40:09 UTC +* Number of recursive dependencies: 135 Run `revdep_details(, "photosynthesis")` for more info @@ -2129,43 +2058,16 @@ Run `revdep_details(, "photosynthesis")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - | - |=================================== | 50% - | - |======================================================================| 100%[ FAIL 6 | WARN 0 | SKIP 0 | PASS 149 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - `Wt1` not equal to `Wt2`. - Attributes: < Modes: list, NULL > - Attributes: < Lengths: 2, 0 > - Attributes: < names for target but not for current > - Attributes: < current is not list-like > - target is units, current is numeric - - [ FAIL 6 | WARN 0 | SKIP 0 | PASS 149 ] - Error: Test failures - Execution halted - ``` - * checking installed package size ... NOTE ``` - installed size is 5.1Mb + installed size is 7.0Mb sub-directories of 1Mb or more: - doc 3.4Mb - help 1.1Mb + doc 6.0Mb ``` -* checking dependencies in R code ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Namespace in Imports field not imported from: ‘future’ - All declared Imports should be used. + Note: found 13 marked UTF-8 strings ``` # phylolm @@ -2193,11 +2095,11 @@ Run `revdep_details(, "phylolm")` for more info
-* Version: 0.11.6 +* Version: 1.0.0 * GitHub: https://github.com/pln-team/PLNmodels * Source code: https://github.com/cran/PLNmodels -* Date/Publication: 2022-02-01 16:00:24 UTC -* Number of recursive dependencies: 173 +* Date/Publication: 2023-01-06 13:20:06 UTC +* Number of recursive dependencies: 146 Run `revdep_details(, "PLNmodels")` for more info @@ -2207,42 +2109,44 @@ Run `revdep_details(, "PLNmodels")` for more info * checking installed package size ... NOTE ``` - installed size is 16.9Mb + installed size is 21.7Mb sub-directories of 1Mb or more: - doc 2.0Mb - libs 13.8Mb + doc 2.1Mb + libs 18.3Mb ``` -# plumber +# portvine
-* Version: 1.1.0 -* GitHub: https://github.com/rstudio/plumber -* Source code: https://github.com/cran/plumber -* Date/Publication: 2021-03-24 05:10:02 UTC -* Number of recursive dependencies: 81 +* Version: 1.0.2 +* GitHub: https://github.com/EmanuelSommer/portvine +* Source code: https://github.com/cran/portvine +* Date/Publication: 2023-01-06 09:40:04 UTC +* Number of recursive dependencies: 129 -Run `revdep_details(, "plumber")` for more info +Run `revdep_details(, "portvine")` for more info
## In both -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 51.3Mb + sub-directories of 1Mb or more: + libs 50.6Mb ``` # ppcseq
-* Version: 1.2.0 +* Version: 1.6.0 * GitHub: https://github.com/stemangiola/ppcseq * Source code: https://github.com/cran/ppcseq -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 117 +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 119 Run `revdep_details(, "ppcseq")` for more info @@ -2252,10 +2156,10 @@ Run `revdep_details(, "ppcseq")` for more info * checking installed package size ... NOTE ``` - installed size is 45.6Mb + installed size is 53.1Mb sub-directories of 1Mb or more: data 1.5Mb - libs 42.8Mb + libs 50.3Mb ``` * checking R code for possible problems ... NOTE @@ -2288,29 +2192,6 @@ Run `revdep_details(, "ppcseq")` for more info GNU make is a SystemRequirements. ``` -# ppseq - -
- -* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/ppseq -* Date/Publication: 2021-09-09 09:00:02 UTC -* Number of recursive dependencies: 100 - -Run `revdep_details(, "ppseq")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.3Mb - sub-directories of 1Mb or more: - doc 5.2Mb - ``` - # prewas
@@ -2319,7 +2200,7 @@ Run `revdep_details(, "ppseq")` for more info * GitHub: https://github.com/Snitkin-Lab-Umich/prewas * Source code: https://github.com/cran/prewas * Date/Publication: 2021-04-02 12:20:05 UTC -* Number of recursive dependencies: 75 +* Number of recursive dependencies: 76 Run `revdep_details(, "prewas")` for more info @@ -2333,35 +2214,33 @@ Run `revdep_details(, "prewas")` for more info ERROR Running the tests in ‘tests/testthat.R’ failed. Last 50 lines of output: - 3. └─future plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) - 4. └─future warn_about_multiprocess(newStack) - 5. └─future warn_about_deprecated(...) - 6. └─base dfcn(msg = msg, package = .packageName) - ── Error (test-reference_alleles.R:89:3): remove_unknown_alleles correctly removes Ns when given valid input ── - + Backtrace: + ▆ + 1. └─prewas:::get_ancestral_alleles(tree = temp_tree, mat = temp_dna_list$variant_only_dna_mat) at test-reference_alleles.R:138:2 + 2. ├─base::t(...) + 3. └─future.apply::future_apply(...) + 4. └─future.apply::future_lapply(...) ... - 1. └─prewas:::get_ancestral_alleles(tree = temp_tree, mat = temp_dna_list$variant_only_dna_mat) at test-reference_alleles.R:258:2 - 2. └─future::plan(future::multiprocess) - 3. └─future plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) - 4. └─future warn_about_multiprocess(newStack) - 5. └─future warn_about_deprecated(...) - 6. └─base dfcn(msg = msg, package = .packageName) + 7. ├─future::run(future) + 8. └─future:::run.Future(future) + 9. ├─base::do.call(makeFuture, args = args) + 10. └─future (local) ``(...) + 11. └─future (local) dfcn(msg = msg, package = .packageName) + 12. └─base::.Defunct(...) [ FAIL 6 | WARN 0 | SKIP 0 | PASS 312 ] Error: Test failures Execution halted ``` -* checking re-building of vignette outputs ... WARNING +* checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: ... --- re-building ‘getting_started_with_prewas.Rmd’ using rmarkdown - Warning in subset_tree_and_matrix(tree, dna_mat) : - These samples were dropped from the matrix: t1 Quitting from lines 136-141 (getting_started_with_prewas.Rmd) Error: processing vignette 'getting_started_with_prewas.Rmd' failed with diagnostics: - Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. + Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is defunct in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. --- failed re-building ‘getting_started_with_prewas.Rmd’ SUMMARY: processing the following file failed: @@ -2379,45 +2258,25 @@ Run `revdep_details(, "prewas")` for more info All declared Imports should be used. ``` -# progressr +# projpred
-* Version: 0.10.0 -* GitHub: https://github.com/HenrikBengtsson/progressr -* Source code: https://github.com/cran/progressr -* Date/Publication: 2021-12-19 03:50:02 UTC -* Number of recursive dependencies: 53 +* Version: 2.3.0 +* GitHub: https://github.com/stan-dev/projpred +* Source code: https://github.com/cran/projpred +* Date/Publication: 2023-01-10 15:00:03 UTC +* Number of recursive dependencies: 143 -Run `revdep_details(, "progressr")` for more info +Run `revdep_details(, "projpred")` for more info
-## Newly broken +## In both -* checking tests ... +* checking package dependencies ... NOTE ``` - Running ‘debug.R’ - Running ‘demo.R’ - ERROR - Running the tests in ‘tests/demo.R’ failed. - Last 50 lines of output: - + - + pp <- 0L - + while (any(sapply(counts, FUN = inherits, "Future"))) { - + counts <- plot_what_is_done(counts) - + } - ... - > close.screen() - [1] 1 2 3 4 5 6 7 8 9 10 11 12 - - > message("SUGGESTION: Try to rerun this demo after changing strategy for how futures are resolved, e.g. plan(multisession).\n") - SUGGESTION: Try to rerun this demo after changing strategy for how futures are resolved, e.g. plan(multisession). - - - plan('multisession') ... DONE - - plan('multiprocess') ... - Error: Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. - Execution halted + Package suggested but not available for checking: ‘cmdstanr’ ``` # promises @@ -2428,7 +2287,7 @@ Run `revdep_details(, "progressr")` for more info * GitHub: https://github.com/rstudio/promises * Source code: https://github.com/cran/promises * Date/Publication: 2021-02-11 19:00:02 UTC -* Number of recursive dependencies: 67 +* Number of recursive dependencies: 68 Run `revdep_details(, "promises")` for more info @@ -2441,89 +2300,15 @@ Run `revdep_details(, "promises")` for more info 'LazyData' is specified without a 'data' directory ``` -# Prostar - -
- -* Version: 1.26.4 -* GitHub: https://github.com/samWieczorek/Prostar -* Source code: https://github.com/cran/Prostar -* Date/Publication: 2022-01-23 -* Number of recursive dependencies: 320 - -Run `revdep_details(, "Prostar")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘BiocManager’ ‘DAPAR’ ‘DAPARdata’ ‘DT’ ‘R.utils’ ‘XML’ ‘colourpicker’ - ‘data.table’ ‘future’ ‘highcharter’ ‘htmlwidgets’ ‘later’ ‘promises’ - ‘rclipboard’ ‘rhandsontable’ ‘sass’ ‘shinyAce’ ‘shinyBS’ ‘shinyTree’ - ‘shinyWidgets’ ‘shinycssloaders’ ‘shinyjqui’ ‘shinyjs’ ‘shinythemes’ - ‘tibble’ ‘webshot’ - All declared Imports should be used. - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Prostar_UserManual.Rnw’ using Sweave - Error: processing vignette 'Prostar_UserManual.Rnw' failed with diagnostics: - Running 'texi2dvi' on 'Prostar_UserManual.tex' failed. - LaTeX errors: - ! LaTeX Error: File `nowidow.sty' not found. - - Type X to quit or to proceed, - or enter new name. (Default extension: sty) - ... - l.189 \RequirePackage - {parnotes}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘Prostar_UserManual.Rnw’ - - SUMMARY: processing the following file failed: - ‘Prostar_UserManual.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# PUMP - -
- -* Version: 1.0.0 -* GitHub: https://github.com/MDRCNY/PUMP -* Source code: https://github.com/cran/PUMP -* Date/Publication: 2022-02-09 09:50:05 UTC -* Number of recursive dependencies: 129 - -Run `revdep_details(, "PUMP")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘here’ - All declared Imports should be used. - ``` - # QDNAseq
-* Version: 1.30.0 +* Version: 1.34.0 * GitHub: https://github.com/ccagc/QDNAseq * Source code: https://github.com/cran/QDNAseq -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 80 +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 88 Run `revdep_details(, "QDNAseq")` for more info @@ -2564,7 +2349,7 @@ Run `revdep_details(, "QDNAseq")` for more info * GitHub: NA * Source code: https://github.com/cran/RAINBOWR * Date/Publication: 2022-01-07 13:53:11 UTC -* Number of recursive dependencies: 147 +* Number of recursive dependencies: 150 Run `revdep_details(, "RAINBOWR")` for more info @@ -2574,50 +2359,9 @@ Run `revdep_details(, "RAINBOWR")` for more info * checking installed package size ... NOTE ``` - installed size is 32.6Mb + installed size is 37.7Mb sub-directories of 1Mb or more: - libs 31.4Mb - ``` - -# rBiasCorrection - -
- -* Version: 0.3.3 -* GitHub: https://github.com/kapsner/rBiasCorrection -* Source code: https://github.com/cran/rBiasCorrection -* Date/Publication: 2022-02-16 13:00:02 UTC -* Number of recursive dependencies: 120 - -Run `revdep_details(, "rBiasCorrection")` for more info - -
- -## Newly broken - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - ── Error (test-algorithm_minmax_FALSE.R:22:5): algorithm test, type 1, minmax = FALSE ── - - Error: Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. - Backtrace: - ▆ - 1. ├─base::suppressWarnings(future::plan("multiprocess")) at test-algorithm_minmax_FALSE.R:22:4 - ... - 2. │ └─base::withCallingHandlers(...) - 3. └─future::plan("multiprocess") - 4. └─future plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) - 5. └─future warn_about_multiprocess(newStack) - 6. └─future warn_about_deprecated(...) - 7. └─base dfcn(msg = msg, package = .packageName) - - [ FAIL 4 | WARN 31 | SKIP 5 | PASS 37 ] - Error: Test failures - Execution halted + libs 36.5Mb ``` # regmedint @@ -2628,7 +2372,7 @@ Run `revdep_details(, "rBiasCorrection")` for more info * GitHub: https://github.com/kaz-yos/regmedint * Source code: https://github.com/cran/regmedint * Date/Publication: 2022-04-06 20:20:02 UTC -* Number of recursive dependencies: 131 +* Number of recursive dependencies: 134 Run `revdep_details(, "regmedint")` for more info @@ -2642,36 +2386,55 @@ Run `revdep_details(, "regmedint")` for more info All declared Imports should be used. ``` -# remiod +# reproducible
-* Version: 1.0.0 -* GitHub: https://github.com/xsswang/remiod -* Source code: https://github.com/cran/remiod -* Date/Publication: 2022-03-14 08:50:02 UTC -* Number of recursive dependencies: 125 +* Version: 1.2.16 +* GitHub: https://github.com/PredictiveEcology/reproducible +* Source code: https://github.com/cran/reproducible +* Date/Publication: 2022-12-22 09:50:02 UTC +* Number of recursive dependencies: 104 -Run `revdep_details(, "remiod")` for more info +Run `revdep_details(, "reproducible")` for more info
## In both -* checking dependencies in R code ... NOTE +* checking tests ... ``` - Namespace in Imports field not imported from: ‘reshape2’ - All declared Imports should be used. + Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 195637 Segmentation fault (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + + ERROR + Running the tests in ‘tests/test-all.R’ failed. + Last 50 lines of output: + adding: scratch/henrik/1120431/Rtmpld0uD2/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) + adding: scratch/henrik/1120431/Rtmpld0uD2/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) + + *** caught segfault *** + address 0x40, cause 'memory not mapped' + ... + 36: doTryCatch(return(expr), name, parentenv, handler) + 37: tryCatchOne(expr, names, parentenv, handlers[[1L]]) + 38: tryCatchList(expr, classes, parentenv, handlers) + 39: tryCatch(code, testthat_abort_reporter = function(cnd) { cat(conditionMessage(cnd), "\n") NULL}) + 40: with_reporter(reporters$multi, lapply(test_paths, test_one_file, env = env, wrap = wrap)) + 41: test_files_serial(test_dir = test_dir, test_package = test_package, test_paths = test_paths, load_helpers = load_helpers, reporter = reporter, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package) + 42: test_files(test_dir = path, test_paths = test_paths, test_package = package, reporter = reporter, load_helpers = load_helpers, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package, parallel = parallel) + 43: test_dir("testthat", package = package, reporter = reporter, ..., load_package = "installed") + 44: test_check("reproducible") + An irrecoverable exception occurred. R is aborting now ... ``` # rgee
-* Version: 1.1.3 +* Version: 1.1.5 * GitHub: https://github.com/r-spatial/rgee * Source code: https://github.com/cran/rgee -* Date/Publication: 2022-03-16 15:50:02 UTC +* Date/Publication: 2022-09-13 08:10:06 UTC * Number of recursive dependencies: 150 Run `revdep_details(, "rgee")` for more info @@ -2682,9 +2445,9 @@ Run `revdep_details(, "rgee")` for more info * checking installed package size ... NOTE ``` - installed size is 8.2Mb + installed size is 7.9Mb sub-directories of 1Mb or more: - doc 7.0Mb + doc 6.6Mb ``` * checking dependencies in R code ... NOTE @@ -2720,56 +2483,15 @@ Run `revdep_details(, "robotstxt")` for more info 'LazyData' is specified without a 'data' directory ``` -# RTransferEntropy - -
- -* Version: 0.2.14 -* GitHub: https://github.com/BZPaper/RTransferEntropy -* Source code: https://github.com/cran/RTransferEntropy -* Date/Publication: 2021-04-02 21:00:03 UTC -* Number of recursive dependencies: 81 - -Run `revdep_details(, "RTransferEntropy")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘transfer-entropy.Rmd’ using rmarkdown - `geom_smooth()` using method = 'gam' and formula 'y ~ s(x, bs = "cs")' - Warning: Removed 1 rows containing non-finite values (stat_smooth). - Warning: Removed 1 rows containing missing values (geom_point). - `geom_smooth()` using method = 'gam' and formula 'y ~ s(x, bs = "cs")' - `geom_smooth()` using method = 'gam' and formula 'y ~ s(x, bs = "cs")' - Warning: Removed 1 rows containing non-finite values (stat_smooth). - Warning: Removed 1 rows containing missing values (geom_point). - ... - Quitting from lines 254-261 (transfer-entropy.Rmd) - Error: processing vignette 'transfer-entropy.Rmd' failed with diagnostics: - Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30] and will soon become defunct. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. In the current R session, 'multiprocess' equals 'multicore'. - --- failed re-building ‘transfer-entropy.Rmd’ - - SUMMARY: processing the following file failed: - ‘transfer-entropy.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # sapfluxnetr
-* Version: 0.1.3 +* Version: 0.1.4 * GitHub: https://github.com/sapfluxnet/sapfluxnetr * Source code: https://github.com/cran/sapfluxnetr -* Date/Publication: 2021-11-19 15:10:02 UTC -* Number of recursive dependencies: 78 +* Date/Publication: 2023-01-25 15:30:02 UTC +* Number of recursive dependencies: 81 Run `revdep_details(, "sapfluxnetr")` for more info @@ -2790,7 +2512,7 @@ Run `revdep_details(, "sapfluxnetr")` for more info * GitHub: NA * Source code: https://github.com/cran/scDiffCom * Date/Publication: 2021-08-17 07:20:05 UTC -* Number of recursive dependencies: 245 +* Number of recursive dependencies: 246 Run `revdep_details(, "scDiffCom")` for more info @@ -2809,11 +2531,11 @@ Run `revdep_details(, "scDiffCom")` for more info
-* Version: 0.3.3 +* Version: 0.3.5 * GitHub: https://github.com/satijalab/sctransform * Source code: https://github.com/cran/sctransform -* Date/Publication: 2022-01-13 08:20:02 UTC -* Number of recursive dependencies: 69 +* Date/Publication: 2022-09-21 17:10:07 UTC +* Number of recursive dependencies: 68 Run `revdep_details(, "sctransform")` for more info @@ -2834,7 +2556,7 @@ Run `revdep_details(, "sctransform")` for more info * GitHub: https://github.com/Abson-dev/sdmApp * Source code: https://github.com/cran/sdmApp * Date/Publication: 2021-07-07 08:30:02 UTC -* Number of recursive dependencies: 167 +* Number of recursive dependencies: 171 Run `revdep_details(, "sdmApp")` for more info @@ -2848,37 +2570,48 @@ Run `revdep_details(, "sdmApp")` for more info All declared Imports should be used. ``` -# seer +# sdmTMB
-* Version: 1.1.7 -* GitHub: https://github.com/thiyangt/seer -* Source code: https://github.com/cran/seer -* Date/Publication: 2021-12-08 05:20:02 UTC -* Number of recursive dependencies: 115 +* Version: 0.3.0 +* GitHub: https://github.com/pbs-assess/sdmTMB +* Source code: https://github.com/cran/sdmTMB +* Date/Publication: 2023-01-28 07:30:02 UTC +* Number of recursive dependencies: 116 -Run `revdep_details(, "seer")` for more info +Run `revdep_details(, "sdmTMB")` for more info
## In both -* checking dependencies in R code ... NOTE +* checking package dependencies ... NOTE ``` - Namespace in Imports field not imported from: ‘MASS’ - All declared Imports should be used. + Package suggested but not available for checking: ‘INLA’ + ``` + +* checking installed package size ... NOTE + ``` + installed size is 78.3Mb + sub-directories of 1Mb or more: + libs 76.6Mb + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘INLA’ ``` # sentopics
-* Version: 0.6.2 +* Version: 0.7.1 * GitHub: https://github.com/odelmarcelle/sentopics * Source code: https://github.com/cran/sentopics -* Date/Publication: 2022-03-15 13:50:02 UTC -* Number of recursive dependencies: 145 +* Date/Publication: 2022-05-18 13:20:02 UTC +* Number of recursive dependencies: 165 Run `revdep_details(, "sentopics")` for more info @@ -2888,11 +2621,10 @@ Run `revdep_details(, "sentopics")` for more info * checking installed package size ... NOTE ``` - installed size is 13.8Mb + installed size is 8.0Mb sub-directories of 1Mb or more: data 1.2Mb - doc 7.4Mb - libs 4.8Mb + libs 6.1Mb ``` * checking Rd cross-references ... NOTE @@ -2909,11 +2641,11 @@ Run `revdep_details(, "sentopics")` for more info
-* Version: 4.1.0 +* Version: 4.3.0 * GitHub: https://github.com/satijalab/seurat * Source code: https://github.com/cran/Seurat -* Date/Publication: 2022-01-14 18:32:42 UTC -* Number of recursive dependencies: 254 +* Date/Publication: 2022-11-18 23:30:08 UTC +* Number of recursive dependencies: 259 Run `revdep_details(, "Seurat")` for more info @@ -2923,10 +2655,10 @@ Run `revdep_details(, "Seurat")` for more info * checking installed package size ... NOTE ``` - installed size is 12.0Mb + installed size is 14.5Mb sub-directories of 1Mb or more: - R 1.3Mb - libs 10.1Mb + R 1.4Mb + libs 12.4Mb ``` * checking Rd cross-references ... NOTE @@ -2934,15 +2666,36 @@ Run `revdep_details(, "Seurat")` for more info Package unavailable to check Rd xrefs: ‘Signac’ ``` +# SeuratObject + +
+ +* Version: 4.1.3 +* GitHub: https://github.com/mojaveazure/seurat-object +* Source code: https://github.com/cran/SeuratObject +* Date/Publication: 2022-11-07 18:50:02 UTC +* Number of recursive dependencies: 57 + +Run `revdep_details(, "SeuratObject")` for more info + +
+ +## In both + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘plotly’ + ``` + # shiny
-* Version: 1.7.1 +* Version: 1.7.4 * GitHub: https://github.com/rstudio/shiny * Source code: https://github.com/cran/shiny -* Date/Publication: 2021-10-02 04:30:02 UTC -* Number of recursive dependencies: 105 +* Date/Publication: 2022-12-15 13:10:02 UTC +* Number of recursive dependencies: 91 Run `revdep_details(, "shiny")` for more info @@ -2952,10 +2705,10 @@ Run `revdep_details(, "shiny")` for more info * checking installed package size ... NOTE ``` - installed size is 9.3Mb + installed size is 9.6Mb sub-directories of 1Mb or more: R 1.6Mb - www 6.6Mb + www 6.9Mb ``` # shiny.worker @@ -2986,67 +2739,107 @@ Run `revdep_details(, "shiny.worker")` for more info 'LazyData' is specified without a 'data' directory ``` -# shinyrecap +# signeR
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/shinyrecap -* Date/Publication: 2019-01-19 23:40:03 UTC -* Number of recursive dependencies: 96 +* Version: 2.0.2 +* GitHub: https://github.com/rvalieris/signeR +* Source code: https://github.com/cran/signeR +* Date/Publication: 2023-01-19 +* Number of recursive dependencies: 242 -Run `revdep_details(, "shinyrecap")` for more info +Run `revdep_details(, "signeR")` for more info
## In both -* checking dependencies in R code ... NOTE +* checking installed package size ... NOTE ``` - Namespaces in Imports field not imported from: - ‘CARE1’ ‘LCMCR’ ‘coda’ ‘conting’ ‘dga’ ‘future’ ‘ggplot2’ ‘ipc’ - ‘promises’ ‘reshape’ ‘shinycssloaders’ ‘testthat’ - All declared Imports should be used. + installed size is 6.6Mb + sub-directories of 1Mb or more: + R 1.1Mb + doc 4.6Mb ``` -* checking LazyData ... NOTE +* checking R code for possible problems ... NOTE ``` - 'LazyData' is specified without a 'data' directory + covariate: no visible binding for global variable ‘.’ + denovo: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg19’ + denovo: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg38’ + explorepage: no visible binding for global variable ‘.’ + fitting: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg19’ + fitting: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg38’ + ... + ExposureCorrelation,SignExp-numeric: no visible binding for global + variable ‘exposure’ + ExposureCorrelation,matrix-numeric: no visible binding for global + variable ‘Feature’ + ExposureCorrelation,matrix-numeric: no visible binding for global + variable ‘exposure’ + Undefined global functions or variables: + . BSgenome.Hsapiens.UCSC.hg19 BSgenome.Hsapiens.UCSC.hg38 Col Feature + Frequency Row Samples Signatures alt<- exposure fc project sig + sig_test + ``` + +* checking Rd files ... NOTE + ``` + prepare_Rd: cosmic_data.Rd:91-93: Dropping empty section \details + prepare_Rd: cosmic_data.Rd:98-100: Dropping empty section \references + prepare_Rd: cosmic_data.Rd:101-102: Dropping empty section \examples + prepare_Rd: tcga_similarities.Rd:96-98: Dropping empty section \details + prepare_Rd: tcga_similarities.Rd:99-101: Dropping empty section \source + prepare_Rd: tcga_similarities.Rd:102-104: Dropping empty section \references + prepare_Rd: tcga_similarities.Rd:105-106: Dropping empty section \examples + prepare_Rd: tcga_tumors.Rd:18-20: Dropping empty section \details + prepare_Rd: tcga_tumors.Rd:21-23: Dropping empty section \source + prepare_Rd: tcga_tumors.Rd:24-26: Dropping empty section \references + prepare_Rd: tcga_tumors.Rd:27-28: Dropping empty section \examples ``` -# simhelpers +# SimDesign
-* Version: 0.1.1 -* GitHub: https://github.com/meghapsimatrix/simhelpers -* Source code: https://github.com/cran/simhelpers -* Date/Publication: 2021-02-14 17:50:02 UTC -* Number of recursive dependencies: 103 +* Version: 2.10.1 +* GitHub: https://github.com/philchalmers/SimDesign +* Source code: https://github.com/cran/SimDesign +* Date/Publication: 2023-02-01 15:30:02 UTC +* Number of recursive dependencies: 104 -Run `revdep_details(, "simhelpers")` for more info +Run `revdep_details(, "SimDesign")` for more info
## In both -* checking dependencies in R code ... NOTE +* checking package dependencies ... NOTE ``` - Namespaces in Imports field not imported from: - ‘future’ ‘magrittr’ ‘purrr’ ‘rlang’ ‘utils’ - All declared Imports should be used. + Package suggested but not available for checking: ‘doMPI’ + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.7Mb + sub-directories of 1Mb or more: + doc 6.2Mb ``` # skpr
-* Version: 1.1.4 +* Version: 1.1.6 * GitHub: https://github.com/tylermorganwall/skpr * Source code: https://github.com/cran/skpr -* Date/Publication: 2022-04-08 19:40:02 UTC -* Number of recursive dependencies: 125 +* Date/Publication: 2022-07-14 10:50:05 UTC +* Number of recursive dependencies: 122 Run `revdep_details(, "skpr")` for more info @@ -3056,9 +2849,9 @@ Run `revdep_details(, "skpr")` for more info * checking installed package size ... NOTE ``` - installed size is 47.8Mb + installed size is 56.7Mb sub-directories of 1Mb or more: - libs 46.3Mb + libs 55.2Mb ``` # solitude @@ -3069,7 +2862,7 @@ Run `revdep_details(, "skpr")` for more info * GitHub: https://github.com/talegari/solitude * Source code: https://github.com/cran/solitude * Date/Publication: 2021-07-29 20:00:02 UTC -* Number of recursive dependencies: 125 +* Number of recursive dependencies: 127 Run `revdep_details(, "solitude")` for more info @@ -3084,83 +2877,15 @@ Run `revdep_details(, "solitude")` for more info All declared Imports should be used. ``` -# spacey - -
- -* Version: 0.1.1 -* GitHub: https://github.com/mikemahoney218/spacey -* Source code: https://github.com/cran/spacey -* Date/Publication: 2020-03-14 18:50:02 UTC -* Number of recursive dependencies: 88 - -Run `revdep_details(, "spacey")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘rgdal’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# SpaDES.core - -
- -* Version: 1.0.10 -* GitHub: https://github.com/PredictiveEcology/SpaDES.core -* Source code: https://github.com/cran/SpaDES.core -* Date/Publication: 2022-01-19 16:22:46 UTC -* Number of recursive dependencies: 152 - -Run `revdep_details(, "SpaDES.core")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘test-all.R’/software/c4/cbi/software/R-4.1.3-gcc8/lib64/R/bin/BATCH: line 60: 230522 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 - - ERROR - Running the tests in ‘tests/test-all.R’ failed. - Last 50 lines of output: - 2b75ecc48000-2b75ece47000 ---p 00005000 00:27 15989972314921970648 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/fastmatch/libs/fastmatch.so - 2b75ece47000-2b75ece48000 r--p 00004000 00:27 15989972314921970648 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/fastmatch/libs/fastmatch.so - 2b75ece48000-2b75ece49000 rw-p 00005000 00:27 15989972314921970648 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/fastmatch/libs/fastmatch.so - 2b75ece49000-2b75ece68000 r-xp 00000000 00:27 4062816005967483540 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/SpaDES.tools/libs/SpaDES.tools.so - 2b75ece68000-2b75ed068000 ---p 0001f000 00:27 4062816005967483540 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/SpaDES.tools/libs/SpaDES.tools.so - ... - 2b75ef27c000-2b75ef47c000 rw-p 00000000 00:00 0 - 2b75ef47c000-2b75ef47d000 ---p 00000000 00:00 0 - 2b75ef47d000-2b75ef67d000 rw-p 00000000 00:00 0 - 2b75ef67d000-2b75ef67f000 r-xp 00000000 00:27 11797017438089374939 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 2b75ef67f000-2b75ef87e000 ---p 00002000 00:27 11797017438089374939 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 2b75ef87e000-2b75ef87f000 r--p 00001000 00:27 11797017438089374939 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 2b75ef87f000-2b75ef880000 rw-p 00002000 00:27 11797017438089374939 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 7ffe823ae000-7ffe82513000 rw-p 00000000 00:00 0 [stack] - 7ffe8252e000-7ffe82530000 r-xp 00000000 00:00 0 [vdso] - ffffffffff600000-ffffffffff601000 r-xp 00000000 00:00 0 [vsyscall] - ``` - # spaMM
-* Version: 3.11.14 +* Version: 4.1.20 * GitHub: NA * Source code: https://github.com/cran/spaMM -* Date/Publication: 2022-04-09 23:30:02 UTC -* Number of recursive dependencies: 100 +* Date/Publication: 2022-12-12 12:50:03 UTC +* Number of recursive dependencies: 122 Run `revdep_details(, "spaMM")` for more info @@ -3170,27 +2895,30 @@ Run `revdep_details(, "spaMM")` for more info * checking package dependencies ... NOTE ``` + Packages suggested but not available for checking: + 'Infusion', 'IsoriX', 'blackbox' + Packages which this enhances but not available for checking: - 'multcomp', 'RLRsim' + 'multcomp', 'RLRsim', 'lmerTest' ``` * checking installed package size ... NOTE ``` - installed size is 46.9Mb + installed size is 55.5Mb sub-directories of 1Mb or more: - R 2.2Mb - libs 43.6Mb + R 2.5Mb + libs 51.8Mb ``` # sparrpowR
-* Version: 0.2.5 +* Version: 0.2.6 * GitHub: https://github.com/machiela-lab/sparrpowR * Source code: https://github.com/cran/sparrpowR -* Date/Publication: 2022-02-05 00:30:02 UTC -* Number of recursive dependencies: 98 +* Date/Publication: 2022-12-02 09:40:09 UTC +* Number of recursive dependencies: 97 Run `revdep_details(, "sparrpowR")` for more info @@ -3209,11 +2937,11 @@ Run `revdep_details(, "sparrpowR")` for more info
-* Version: 1.1.0 +* Version: 1.2.0 * GitHub: https://github.com/NAU-CCL/SPARSEMODr * Source code: https://github.com/cran/SPARSEMODr -* Date/Publication: 2021-07-01 17:50:02 UTC -* Number of recursive dependencies: 119 +* Date/Publication: 2022-07-19 20:50:02 UTC +* Number of recursive dependencies: 122 Run `revdep_details(, "SPARSEMODr")` for more info @@ -3232,11 +2960,11 @@ Run `revdep_details(, "SPARSEMODr")` for more info
-* Version: 1.2.0 +* Version: 1.2.2 * GitHub: https://github.com/FridleyLab/spatialTIME * Source code: https://github.com/cran/spatialTIME -* Date/Publication: 2021-09-11 04:10:02 UTC -* Number of recursive dependencies: 120 +* Date/Publication: 2022-11-22 17:30:02 UTC +* Number of recursive dependencies: 91 Run `revdep_details(, "spatialTIME")` for more info @@ -3247,7 +2975,7 @@ Run `revdep_details(, "spatialTIME")` for more info * checking dependencies in R code ... NOTE ``` Namespaces in Imports field not imported from: - ‘ggpubr’ ‘pheatmap’ ‘rlist’ ‘stats’ ‘viridis’ + ‘gridExtra’ ‘pheatmap’ All declared Imports should be used. ``` @@ -3259,7 +2987,7 @@ Run `revdep_details(, "spatialTIME")` for more info * GitHub: https://github.com/spatial-ews/spatialwarnings * Source code: https://github.com/cran/spatialwarnings * Date/Publication: 2022-03-21 13:00:02 UTC -* Number of recursive dependencies: 84 +* Number of recursive dependencies: 98 Run `revdep_details(, "spatialwarnings")` for more info @@ -3277,9 +3005,9 @@ Run `revdep_details(, "spatialwarnings")` for more info * checking installed package size ... NOTE ``` - installed size is 6.4Mb + installed size is 6.8Mb sub-directories of 1Mb or more: - libs 5.4Mb + libs 5.8Mb ``` # sphunif @@ -3290,7 +3018,7 @@ Run `revdep_details(, "spatialwarnings")` for more info * GitHub: https://github.com/egarpor/sphunif * Source code: https://github.com/cran/sphunif * Date/Publication: 2021-09-02 07:40:02 UTC -* Number of recursive dependencies: 72 +* Number of recursive dependencies: 74 Run `revdep_details(, "sphunif")` for more info @@ -3300,9 +3028,9 @@ Run `revdep_details(, "sphunif")` for more info * checking installed package size ... NOTE ``` - installed size is 20.5Mb + installed size is 24.2Mb sub-directories of 1Mb or more: - libs 19.6Mb + libs 23.3Mb ``` * checking data for non-ASCII characters ... NOTE @@ -3314,11 +3042,11 @@ Run `revdep_details(, "sphunif")` for more info
-* Version: 0.4.3.1 +* Version: 0.4.3.6 * GitHub: https://github.com/JeremyGelb/spNetwork * Source code: https://github.com/cran/spNetwork -* Date/Publication: 2022-04-23 23:50:02 UTC -* Number of recursive dependencies: 148 +* Date/Publication: 2022-11-11 08:10:02 UTC +* Number of recursive dependencies: 149 Run `revdep_details(, "spNetwork")` for more info @@ -3328,22 +3056,46 @@ Run `revdep_details(, "spNetwork")` for more info * checking installed package size ... NOTE ``` - installed size is 18.6Mb + installed size is 25.2Mb sub-directories of 1Mb or more: - doc 1.1Mb + doc 1.0Mb extdata 2.6Mb - libs 13.5Mb + libs 20.3Mb + ``` + +# squat + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/squat +* Date/Publication: 2022-12-22 11:20:02 UTC +* Number of recursive dependencies: 123 + +Run `revdep_details(, "squat")` for more info + +
+ +## In both + +* checking installed package size ... NOTE + ``` + installed size is 18.6Mb + sub-directories of 1Mb or more: + data 1.1Mb + libs 16.6Mb ``` # ssdtools
-* Version: 1.0.1 +* Version: 1.0.2 * GitHub: https://github.com/bcgov/ssdtools * Source code: https://github.com/cran/ssdtools -* Date/Publication: 2022-04-10 21:40:02 UTC -* Number of recursive dependencies: 141 +* Date/Publication: 2022-05-14 23:50:02 UTC +* Number of recursive dependencies: 144 Run `revdep_details(, "ssdtools")` for more info @@ -3353,21 +3105,21 @@ Run `revdep_details(, "ssdtools")` for more info * checking installed package size ... NOTE ``` - installed size is 17.6Mb + installed size is 23.0Mb sub-directories of 1Mb or more: doc 1.2Mb - libs 15.1Mb + libs 20.6Mb ``` # stars
-* Version: 0.5-5 +* Version: 0.6-0 * GitHub: https://github.com/r-spatial/stars * Source code: https://github.com/cran/stars -* Date/Publication: 2021-12-19 03:20:02 UTC -* Number of recursive dependencies: 148 +* Date/Publication: 2022-11-21 13:10:02 UTC +* Number of recursive dependencies: 153 Run `revdep_details(, "stars")` for more info @@ -3382,21 +3134,21 @@ Run `revdep_details(, "stars")` for more info * checking installed package size ... NOTE ``` - installed size is 8.6Mb + installed size is 6.0Mb sub-directories of 1Mb or more: - doc 2.3Mb - nc 4.5Mb + doc 2.4Mb + nc 1.7Mb ``` # synergyfinder
-* Version: 3.2.10 +* Version: 3.6.2 * GitHub: NA * Source code: https://github.com/cran/synergyfinder -* Date/Publication: 2022-03-31 -* Number of recursive dependencies: 181 +* Date/Publication: 2022-12-22 +* Number of recursive dependencies: 191 Run `revdep_details(, "synergyfinder")` for more info @@ -3412,31 +3164,6 @@ Run `revdep_details(, "synergyfinder")` for more info All declared Imports should be used. ``` -* checking for code/documentation mismatches ... WARNING - ``` - Codoc mismatches from documentation object 'PlotDoseResponse': - PlotDoseResponse - Code: function(data, block_ids = c(1), drugs = c(1, 2), adjusted = - TRUE, statistic = NULL, summary_statistic = "mean", - high_value_color = "#FF0000", low_value_color = - "#00FF00", point_color = "#C24B40", curve_color = - "black", curve_ylim = NULL, curve_grid = TRUE, - text_size_scale = 1, heatmap_text_label_size_scale = - 1, heatmap_text_label_color = "#000000", - heatmap_color_range = NULL, curve_plot_title = NULL, - ... - high_value_color = "#A90217", low_value_color = - "#2166AC", text_size_scale = 1, - heatmap_text_label_size_scale = 1, - heatmap_text_label_color = "#000000", grid = TRUE, - dynamic = FALSE, display = TRUE, save_file = FALSE, - file_type = "pdf", file_name = NULL, file_path = NULL, - height = 6, width = 6, units = "in") - Mismatches in argument default values: - Name: 'high_value_color' Code: "#FF0000" Docs: "#A90217" - Name: 'low_value_color' Code: "#00FF00" Docs: "#2166AC" - ``` - * checking installed package size ... NOTE ``` installed size is 6.0Mb @@ -3473,11 +3200,11 @@ Run `revdep_details(, "synergyfinder")` for more info
-* Version: 1.1.1 +* Version: 1.1.2 * GitHub: https://github.com/frictionlessdata/tableschema-r * Source code: https://github.com/cran/tableschema.r -* Date/Publication: 2020-03-12 12:40:02 UTC -* Number of recursive dependencies: 65 +* Date/Publication: 2022-09-29 20:00:03 UTC +* Number of recursive dependencies: 66 Run `revdep_details(, "tableschema.r")` for more info @@ -3485,31 +3212,20 @@ Run `revdep_details(, "tableschema.r")` for more info ## In both -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘iterators’ - All declared Imports should be used. - ``` - * checking Rd cross-references ... NOTE ``` Package unavailable to check Rd xrefs: ‘parsedate’ ``` -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - # targeted
-* Version: 0.2.0 +* Version: 0.3 * GitHub: https://github.com/kkholst/targeted * Source code: https://github.com/cran/targeted -* Date/Publication: 2021-10-26 14:40:02 UTC -* Number of recursive dependencies: 76 +* Date/Publication: 2022-10-25 20:30:02 UTC +* Number of recursive dependencies: 94 Run `revdep_details(, "targeted")` for more info @@ -3519,20 +3235,20 @@ Run `revdep_details(, "targeted")` for more info * checking installed package size ... NOTE ``` - installed size is 13.6Mb + installed size is 16.8Mb sub-directories of 1Mb or more: - libs 12.7Mb + libs 15.7Mb ``` # text
-* Version: 0.9.50 +* Version: 0.9.99.2 * GitHub: https://github.com/OscarKjell/text * Source code: https://github.com/cran/text -* Date/Publication: 2022-02-12 23:10:02 UTC -* Number of recursive dependencies: 148 +* Date/Publication: 2022-09-20 22:00:02 UTC +* Number of recursive dependencies: 150 Run `revdep_details(, "text")` for more info @@ -3549,11 +3265,11 @@ Run `revdep_details(, "text")` for more info
-* Version: 1.1.1 +* Version: 1.2.0 * GitHub: https://github.com/ms609/TreeSearch * Source code: https://github.com/cran/TreeSearch -* Date/Publication: 2022-03-22 10:10:28 UTC -* Number of recursive dependencies: 115 +* Date/Publication: 2022-08-10 22:40:17 UTC +* Number of recursive dependencies: 117 Run `revdep_details(, "TreeSearch")` for more info @@ -3561,12 +3277,37 @@ Run `revdep_details(, "TreeSearch")` for more info ## In both +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + --- re-building ‘custom.Rmd’ using rmarkdown + Error reading bibliography file ../inst/REFERENCES.bib: + (line 348, column 1): + unexpected '@' + Error: processing vignette 'custom.Rmd' failed with diagnostics: + pandoc document conversion failed with error 25 + --- failed re-building ‘custom.Rmd’ + + --- re-building ‘getting-started.Rmd’ using rmarkdown + ... + unexpected '@' + Error: processing vignette 'tree-search.Rmd' failed with diagnostics: + pandoc document conversion failed with error 25 + --- failed re-building ‘tree-search.Rmd’ + + SUMMARY: processing the following files failed: + ‘custom.Rmd’ ‘profile-scores.Rmd’ ‘profile.Rmd’ ‘tree-search.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + * checking installed package size ... NOTE ``` - installed size is 5.8Mb + installed size is 6.3Mb sub-directories of 1Mb or more: datasets 1.6Mb - libs 2.2Mb + libs 2.4Mb ``` # TriDimRegression @@ -3577,7 +3318,7 @@ Run `revdep_details(, "TreeSearch")` for more info * GitHub: https://github.com/alexander-pastukhov/tridim-regression * Source code: https://github.com/cran/TriDimRegression * Date/Publication: 2021-10-05 08:30:08 UTC -* Number of recursive dependencies: 98 +* Number of recursive dependencies: 100 Run `revdep_details(, "TriDimRegression")` for more info @@ -3587,9 +3328,9 @@ Run `revdep_details(, "TriDimRegression")` for more info * checking installed package size ... NOTE ``` - installed size is 41.3Mb + installed size is 47.3Mb sub-directories of 1Mb or more: - libs 40.7Mb + libs 46.8Mb ``` * checking dependencies in R code ... NOTE @@ -3604,27 +3345,6 @@ Run `revdep_details(, "TriDimRegression")` for more info GNU make is a SystemRequirements. ``` -# tsfeatures - -
- -* Version: 1.0.2 -* GitHub: https://github.com/robjhyndman/tsfeatures -* Source code: https://github.com/cran/tsfeatures -* Date/Publication: 2020-06-07 16:10:02 UTC -* Number of recursive dependencies: 98 - -Run `revdep_details(, "tsfeatures")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - # TSstudio
@@ -3633,7 +3353,7 @@ Run `revdep_details(, "tsfeatures")` for more info * GitHub: https://github.com/RamiKrispin/TSstudio * Source code: https://github.com/cran/TSstudio * Date/Publication: 2020-01-21 05:30:02 UTC -* Number of recursive dependencies: 142 +* Number of recursive dependencies: 156 Run `revdep_details(, "TSstudio")` for more info @@ -3655,7 +3375,7 @@ Run `revdep_details(, "TSstudio")` for more info * GitHub: https://github.com/nhejazi/txshift * Source code: https://github.com/cran/txshift * Date/Publication: 2022-02-09 22:30:02 UTC -* Number of recursive dependencies: 110 +* Number of recursive dependencies: 111 Run `revdep_details(, "txshift")` for more info @@ -3672,11 +3392,11 @@ Run `revdep_details(, "txshift")` for more info
-* Version: 1.1.7 +* Version: 1.1.9 * GitHub: https://github.com/openbiox/UCSCXenaShiny * Source code: https://github.com/cran/UCSCXenaShiny -* Date/Publication: 2022-04-13 07:52:38 UTC -* Number of recursive dependencies: 187 +* Date/Publication: 2022-12-12 09:00:03 UTC +* Number of recursive dependencies: 181 Run `revdep_details(, "UCSCXenaShiny")` for more info @@ -3686,9 +3406,9 @@ Run `revdep_details(, "UCSCXenaShiny")` for more info * checking installed package size ... NOTE ``` - installed size is 6.0Mb + installed size is 6.6Mb sub-directories of 1Mb or more: - doc 1.1Mb + doc 1.4Mb shinyapp 3.3Mb ``` @@ -3696,10 +3416,10 @@ Run `revdep_details(, "UCSCXenaShiny")` for more info
-* Version: 2.1.2 +* Version: 2.1.3 * GitHub: https://github.com/dcgerard/updog * Source code: https://github.com/cran/updog -* Date/Publication: 2022-01-24 21:50:02 UTC +* Date/Publication: 2022-10-18 08:00:02 UTC * Number of recursive dependencies: 145 Run `revdep_details(, "updog")` for more info @@ -3710,9 +3430,9 @@ Run `revdep_details(, "updog")` for more info * checking installed package size ... NOTE ``` - installed size is 6.7Mb + installed size is 7.9Mb sub-directories of 1Mb or more: - libs 6.0Mb + libs 7.1Mb ``` # vmeasur @@ -3723,7 +3443,7 @@ Run `revdep_details(, "updog")` for more info * GitHub: NA * Source code: https://github.com/cran/vmeasur * Date/Publication: 2021-11-11 19:00:02 UTC -* Number of recursive dependencies: 122 +* Number of recursive dependencies: 117 Run `revdep_details(, "vmeasur")` for more info @@ -3738,15 +3458,45 @@ Run `revdep_details(, "vmeasur")` for more info See ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/00install.out’ for details. ``` +# wru + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/kosukeimai/wru +* Source code: https://github.com/cran/wru +* Date/Publication: 2022-10-21 17:30:02 UTC +* Number of recursive dependencies: 87 + +Run `revdep_details(, "wru")` for more info + +
+ +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.6Mb + sub-directories of 1Mb or more: + data 3.5Mb + libs 1.9Mb + ``` + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘future’ + All declared Imports should be used. + ``` + # XNAString
-* Version: 1.2.2 +* Version: 1.6.0 * GitHub: NA * Source code: https://github.com/cran/XNAString -* Date/Publication: 2021-11-30 -* Number of recursive dependencies: 98 +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 101 Run `revdep_details(, "XNAString")` for more info @@ -3756,9 +3506,9 @@ Run `revdep_details(, "XNAString")` for more info * checking installed package size ... NOTE ``` - installed size is 10.8Mb + installed size is 11.2Mb sub-directories of 1Mb or more: - libs 9.7Mb + libs 9.5Mb ``` * checking top-level files ... NOTE From 566cb9ba53103630e56830c6779c96f5f73a5759 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 2 Feb 2023 14:43:19 -0800 Subject: [PATCH 49/88] REVDEP: 276 packages; one last run with R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent making sure we're all good [ci skip] --- revdep/README.md | 20 +- .../README.md | 273 -- .../cran.md | 7 - .../failures.md | 1 - .../notes.md | 45 - .../problems.md | 3322 ----------------- revdep/problems.md | 202 +- 7 files changed, 181 insertions(+), 3689 deletions(-) delete mode 100644 revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/README.md delete mode 100644 revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/cran.md delete mode 100644 revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/failures.md delete mode 100644 revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/notes.md delete mode 100644 revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/problems.md diff --git a/revdep/README.md b/revdep/README.md index 6f70200a..01ac23fd 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,15 +10,15 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-01 | +|date |2023-02-02 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.30.0-9026 |* | -|codetools |0.2-18 |0.2-18 | | +|future |1.31.0 |1.31.0-9002 |* | +|codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | |listenv |0.9.0 |0.9.0 | | @@ -33,7 +33,7 @@ |[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | |alookr |0.3.7 | | | | |alphaci |1.0.0 | | | | -|[AlpsNMR](problems.md#alpsnmr)|4.0.2 |2 | | | +|[AlpsNMR](problems.md#alpsnmr)|4.0.2 |3 | | | |arkdb |0.0.16 | | | | |aroma.affymetrix |3.2.1 | | | | |aroma.cn |1.7.0 | | | | @@ -89,7 +89,7 @@ |easyalluvial |0.3.1 | | | | |[EFAtools](problems.md#efatools)|0.4.4 | | |2 | |elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.15 | |1 | | +|[envi](problems.md#envi) |0.1.17 | |1 | | |[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | |epwshiftr |0.1.3 | | | | |ezcox |1.0.2 | | | | @@ -125,7 +125,7 @@ |gtfs2emis |0.1.0 | | | | |gtfs2gps |2.1-0 | | | | |[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 |2 | |1 | |hacksig |0.1.2 | | | | |[hal9001](problems.md#hal9001)|0.4.3 | | |1 | |haldensify |0.2.3 | | | | @@ -191,8 +191,8 @@ |nflseedR |1.2.0 | | | | |nncc |1.0.0 | | | | |[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | -|onemapsgapi |1.1.0 | | | | -|[OOS](problems.md#oos) |1.0.0 | | |1 | +|[onemapsgapi](problems.md#onemapsgapi)|1.1.0 |1 | | | +|[OOS](problems.md#oos) |1.0.0 |1 | |1 | |origami |1.0.7 | | | | |paramsim |0.1.0 | | | | |[partR2](problems.md#partr2)|0.9.1 | | |1 | @@ -246,7 +246,7 @@ |[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | |seer |1.1.8 | | | | |semtree |0.9.18 | | | | -|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[sentopics](problems.md#sentopics)|0.7.1 |1 | |3 | |[Seurat](problems.md#seurat)|4.3.0 | | |2 | |[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | |[shiny](problems.md#shiny)|1.7.4 | | |1 | @@ -266,7 +266,7 @@ |[solitude](problems.md#solitude)|1.1.3 | | |1 | |sovereign |1.2.1 | | | | |[spaMM](problems.md#spamm)|4.1.20 | | |2 | -|[sparrpowR](problems.md#sparrpowr)|0.2.6 | |1 | | +|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | |[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | |[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | |[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/README.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/README.md deleted file mode 100644 index c340e029..00000000 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/README.md +++ /dev/null @@ -1,273 +0,0 @@ -# Platform - -|field |value | -|:--------|:-------------------------------------------------------| -|version |R version 4.1.3 (2022-03-10) | -|os |CentOS Linux 7 (Core) | -|system |x86_64, linux-gnu | -|ui |X11 | -|language |en | -|collate |en_US.UTF-8 | -|ctype |en_US.UTF-8 | -|tz |America/Los_Angeles | -|date |2022-04-28 | -|pandoc |2.18 @ /software/c4/cbi/software/pandoc-2.18/bin/pandoc | - -# Dependencies - -|package |old |new |Δ | -|:----------|:------|:-----------|:--| -|future |1.25.0 |1.25.0-9004 |* | -|codetools |0.2-18 |0.2-18 | | -|digest |0.6.29 |0.6.29 | | -|globals |0.14.0 |0.14.0 | | -|listenv |0.8.0 |0.8.0 | | -|parallelly |1.31.1 |1.31.1 | | - -# Revdeps - -## All (240) - -|package |version |error |warning |note | -|:--------------------------------------------------------|:---------|:-----|:-------|:----| -|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | -|alookr |0.3.5 | | | | -|[AlpsNMR](problems.md#alpsnmr) |3.4.0 | | |1 | -|arkdb |0.0.15 | | | | -|aroma.affymetrix |3.2.0 | | | | -|[aroma.core](problems.md#aromacore) |3.2.2 | | |1 | -|[BAMBI](problems.md#bambi) |2.3.3 | | |2 | -|[baseballr](problems.md#baseballr) |1.2.0 | | |1 | -|[BatchGetSymbols](problems.md#batchgetsymbols) |2.6.1 | | |1 | -|batchtools |0.9.15 | | | | -|bayesian |0.0.8 | | | | -|bayesmove |0.2.1 | | | | -|[bcmaps](problems.md#bcmaps) |1.0.2 | | |1 | -|[BEKKs](problems.md#bekks) |1.1.0 | | |2 | -|bhmbasket |0.9.5 | | | | -|[bigDM](problems.md#bigdm) |0.4.1 | | |2 | -|[bistablehistory](problems.md#bistablehistory) |1.1.1 | | |3 | -|bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan) |0.4-1 | | |2 | -|[blockCV](problems.md#blockcv) |2.1.4 | | |2 | -|bolasso |0.1.0 | | | | -|[brms](problems.md#brms) |2.17.0 | | |2 | -|ceRNAnetsim |1.6.99 | | | | -|[cfbfastR](problems.md#cfbfastr) |1.6.4 | | |1 | -|[ChromSCape](problems.md#chromscape) |1.4.0 | | |5 | -|[civis](problems.md#civis) |3.0.0 | | |1 | -|Clustering |1.7.6 | | | | -|codalm |0.1.2 | | | | -|[codebook](problems.md#codebook) |0.9.2 | | |3 | -|conformalInference.fd |1.1.1 | | | | -|conformalInference.multi |1.1.1 | | | | -|crossmap |0.3.0 | | | | -|[cSEM](problems.md#csem) |0.4.0 | | |1 | -|[CSGo](problems.md#csgo) |0.6.7 | | |1 | -|cvCovEst |1.0.2 | | | | -|[datapackage.r](problems.md#datapackager) |1.3.5 |1 | |1 | -|DeclareDesign |0.30.0 | | | | -|[delayed](problems.md#delayed) |0.3.0 | | |2 | -|dhReg |0.1.1 | | | | -|[dipsaus](problems.md#dipsaus) |0.2.0 | | |1 | -|disk.frame |0.7.2 | | | | -|[dispositionEffect](problems.md#dispositioneffect) |1.0.0 |1 | | | -|doFuture |0.12.2 | | | | -|DQAstats |0.2.6 | | | | -|[dragon](problems.md#dragon) |1.2.1 | | |1 | -|drake |7.13.3 | | | | -|drimmR |1.0.1 | | | | -|drtmle |1.1.1 | | | | -|[easyalluvial](problems.md#easyalluvial) |0.3.0 | | |1 | -|[EFAtools](problems.md#efatools) |0.4.1 | | |2 | -|elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.13 | |1 | | -|[EpiNow2](problems.md#epinow2) |1.3.2 | | |2 | -|[epitweetr](problems.md#epitweetr) |2.0.3 | | |3 | -|epwshiftr |0.1.3 | | | | -|EWCE |1.2.0 | | | | -|ezcox |1.0.2 | | | | -|fabletools |0.3.2 | | | | -|FAMoS |0.3.0 | | | | -|fastpos |0.4.1 | | | | -|fastRhockey |0.3.0 | | | | -|fiery |1.1.3 | | | | -|finbif |0.6.4 | | | | -|[fipe](problems.md#fipe) |0.0.1 | | |1 | -|[flowGraph](problems.md#flowgraph) |1.2.0 | |1 |2 | -|[foieGras](problems.md#foiegras) |0.7-6 | | |1 | -|[forecastML](problems.md#forecastml) |0.9.0 | | |1 | -|fundiversity |0.2.1 | | | | -|funGp |0.2.2 | | | | -|furrr |0.2.3 | | | | -|future.apply |1.9.0 | | | | -|future.batchtools |0.10.0 | | | | -|future.callr |0.8.0 | | | | -|future.tests |0.3.0 | | | | -|fxTWAPLS |0.1.0 | | | | -|genBaRcode |1.2.4 | | | | -|[geocmeans](problems.md#geocmeans) |0.2.0 | | |2 | -|[GetBCBData](problems.md#getbcbdata) |0.6 | | |2 | -|[googleComputeEngineR](problems.md#googlecomputeenginer) |0.3.0 | | |1 | -|googlePubsubR |0.0.3 | | | | -|[googleTagManageR](problems.md#googletagmanager) |0.2.0 | | |1 | -|[grattan](problems.md#grattan) |1.9.0.10 | | |2 | -|[greed](problems.md#greed) |0.6.0 | | |2 | -|greta |0.4.2 | | | | -|gstat |2.0-9 | | | | -|GSVA |1.42.0 | | | | -|gsynth |1.2.1 | | | | -|gtfs2gps |2.0-2 | | | | -|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews) |0.1.0 | | |1 | -|hacksig |0.1.2 | | | | -|[hal9001](problems.md#hal9001) |0.4.3 | | |1 | -|haldensify |0.2.3 | | | | -|hoopR |1.5.0 | | | | -|[hwep](problems.md#hwep) |0.0.1 | | |1 | -|idmodelr |0.3.2 | | | | -|IFAA |1.0.6 | | | | -|[iml](problems.md#iml) |0.10.1 | | |1 | -|incubate |1.1.6 | | | | -|[infercnv](problems.md#infercnv) |1.10.1 | | |2 | -|[inlinedocs](problems.md#inlinedocs) |2019.12.5 | | |1 | -|interflex |1.2.6 | | | | -|[ipc](problems.md#ipc) |0.1.3 | | |1 | -|isoreader |1.3.2 | | | | -|[ivmte](problems.md#ivmte) |1.4.0 | | |1 | -|JointAI |1.0.3 | | | | -|jstor |0.3.10 | | | | -|JuliaConnectoR |1.1.1 | | | | -|[kernelboot](problems.md#kernelboot) |0.1.7 | | |1 | -|[keyATM](problems.md#keyatm) |0.4.0 | | |1 | -|[lava](problems.md#lava) |1.6.10 | | |1 | -|ldaPrototype |0.3.1 | | | | -|ldsr |0.0.2 | | | | -|lemna |0.9.2 | | | | -|LexFindR |1.0.2 | | | | -|lgr |0.4.3 | | | | -|[lidR](problems.md#lidr) |4.0.0 |2 | |1 | -|lightr |1.6.2 | | | | -|[lmtp](problems.md#lmtp) |1.0.0 | | |1 | -|LWFBrook90R |0.4.5 | | | | -|[MAI](problems.md#mai) |1.0.0 | | |1 | -|MAMS |2.0.0 | | | | -|mcmcensemble |3.0.0 | | | | -|mcp |0.3.2 | | | | -|merTools |0.5.2 | | | | -|[microservices](problems.md#microservices) |0.1.2 |1 | |1 | -|microSTASIS |0.1.0 | | | | -|migraph |0.9.3 | | | | -|mikropml |1.2.2 | | | | -|[MineICA](problems.md#mineica) |1.34.0 | |2 |5 | -|[missSBM](problems.md#misssbm) |1.0.2 | | |1 | -|mistyR |1.2.1 | | | | -|mlr3 |0.13.3 | | | | -|mlr3db |0.4.2 | | | | -|mlr3spatial |0.1.2 | | | | -|[momentuHMM](problems.md#momentuhmm) |1.5.4 | | |1 | -|MOSS |0.2.2 | | | | -|mrgsim.parallel |0.2.1 | | | | -|nfl4th |1.0.1 | | | | -|nflfastR |4.3.0 | | | | -|nflseedR |1.0.2 | | | | -|NMproject |0.6.7 | | | | -|[onemapsgapi](problems.md#onemapsgapi) |1.0.0 | | |1 | -|[OOS](problems.md#oos) |1.0.0 | | |1 | -|origami |1.0.5 | | | | -|[partR2](problems.md#partr2) |0.9.1 | | |1 | -|[pavo](problems.md#pavo) |2.7.1 | |1 | | -|PCRedux |1.1 | | | | -|PeakSegDisk |2022.2.1 | | | | -|penaltyLearning |2020.5.13 | | | | -|[photosynthesis](problems.md#photosynthesis) |2.0.1 |1 | |2 | -|[phylolm](problems.md#phylolm) |2.6.2 | | |1 | -|[PLNmodels](problems.md#plnmodels) |0.11.6 | | |1 | -|[plumber](problems.md#plumber) |1.1.0 | | |1 | -|[ppcseq](problems.md#ppcseq) |1.2.0 | | |3 | -|[ppseq](problems.md#ppseq) |0.1.1 | | |1 | -|[prewas](problems.md#prewas) |1.1.1 | | |1 | -|progressr |0.10.0 | | | | -|projpred |2.1.1 | | | | -|[promises](problems.md#promises) |1.2.0.1 | | |1 | -|[Prostar](problems.md#prostar) |1.26.4 | | |2 | -|protti |0.3.0 | | | | -|PSCBS |0.66.0 | | | | -|[PUMP](problems.md#pump) |1.0.0 | | |1 | -|[QDNAseq](problems.md#qdnaseq) |1.30.0 | | |1 | -|qgcomp |2.8.6 | | | | -|qgcompint |0.7.0 | | | | -|[RAINBOWR](problems.md#rainbowr) |0.1.29 | | |1 | -|rangeMapper |2.0.2 | | | | -|rBiasCorrection |0.3.3 | | | | -|refineR |1.0.0 | | | | -|[regmedint](problems.md#regmedint) |1.0.0 | | |1 | -|[remiod](problems.md#remiod) |1.0.0 | | |1 | -|reproducible |1.2.8 | | | | -|reval |3.0-0 | | | | -|[rgee](problems.md#rgee) |1.1.3 | | |2 | -|[robotstxt](problems.md#robotstxt) |0.7.13 | | |2 | -|robust2sls |0.2.0 | | | | -|RTransferEntropy |0.2.14 | | | | -|[sapfluxnetr](problems.md#sapfluxnetr) |0.1.3 | | |1 | -|[scDiffCom](problems.md#scdiffcom) |0.1.0 | | |1 | -|SCtools |0.3.1 | | | | -|[sctransform](problems.md#sctransform) |0.3.3 | | |1 | -|[sdmApp](problems.md#sdmapp) |0.0.2 | | |1 | -|[seer](problems.md#seer) |1.1.7 | | |1 | -|semtree |0.9.17 | | | | -|[sentopics](problems.md#sentopics) |0.6.2 | | |3 | -|[Seurat](problems.md#seurat) |4.1.0 | | |2 | -|shar |1.3.2 | | | | -|[shiny](problems.md#shiny) |1.7.1 | | |1 | -|[shiny.worker](problems.md#shinyworker) |0.0.1 | | |2 | -|[shinyrecap](problems.md#shinyrecap) |0.1.0 | | |2 | -|sigminer |2.1.4 | | | | -|Signac |1.6.0 | | | | -|simfinapi |0.2.0 | | | | -|simglm |0.8.9 | | | | -|[simhelpers](problems.md#simhelpers) |0.1.1 | | |1 | -|sims |0.0.3 | | | | -|skewlmm |1.0.0 | | | | -|[skpr](problems.md#skpr) |1.1.4 | | |1 | -|smoots |1.1.3 | | | | -|sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude) |1.1.3 | | |1 | -|sovereign |1.2.1 | | | | -|[spacey](problems.md#spacey) |0.1.1 | | |2 | -|[SpaDES.core](problems.md#spadescore) |1.0.10 |1 | | | -|[spaMM](problems.md#spamm) |3.11.14 | | |2 | -|[sparrpowR](problems.md#sparrpowr) |0.2.5 | |1 | | -|[SPARSEMODr](problems.md#sparsemodr) |1.1.0 | | |1 | -|[spatialTIME](problems.md#spatialtime) |1.2.0 | | |1 | -|[spatialwarnings](problems.md#spatialwarnings) |3.0.3 | |1 |1 | -|sperrorest |3.0.4 | | | | -|[sphunif](problems.md#sphunif) |1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork) |0.4.3.1 | | |1 | -|[ssdtools](problems.md#ssdtools) |1.0.1 | | |1 | -|[stars](problems.md#stars) |0.5-5 | | |2 | -|startR |2.2.0 | | | | -|steps |1.2.1 | | | | -|supercells |0.8.2 | | | | -|[synergyfinder](problems.md#synergyfinder) |3.2.10 | |2 |2 | -|[tableschema.r](problems.md#tableschemar) |1.1.1 | | |3 | -|[targeted](problems.md#targeted) |0.2.0 | | |1 | -|targets |0.12.0 | | | | -|tcensReg |0.1.7 | | | | -|tcplfit2 |0.1.3 | | | | -|tealeaves |1.0.5 | | | | -|[text](problems.md#text) |0.9.50 | | |1 | -|tglkmeans |0.3.4 | | | | -|tidyqwi |0.1.2 | | | | -|TKCat |0.7.1 | | | | -|[TreeSearch](problems.md#treesearch) |1.1.1 | | |1 | -|[TriDimRegression](problems.md#tridimregression) |1.0.1 | | |3 | -|[tsfeatures](problems.md#tsfeatures) |1.0.2 | | |1 | -|[TSstudio](problems.md#tsstudio) |0.1.6 | | |1 | -|[txshift](problems.md#txshift) |0.3.8 | | |1 | -|[UCSCXenaShiny](problems.md#ucscxenashiny) |1.1.7 | | |1 | -|[updog](problems.md#updog) |2.1.2 | | |1 | -|[vmeasur](problems.md#vmeasur) |0.1.4 | |1 | | -|wehoop |1.2.1 | | | | -|[XNAString](problems.md#xnastring) |1.2.2 | | |3 | - diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/cran.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/cran.md deleted file mode 100644 index 3acc5f76..00000000 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/cran.md +++ /dev/null @@ -1,7 +0,0 @@ -## revdepcheck results - -We checked 240 reverse dependencies (225 from CRAN + 15 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - - * We saw 0 new problems - * We failed to check 0 packages - diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/failures.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/failures.md deleted file mode 100644 index 9a207363..00000000 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/failures.md +++ /dev/null @@ -1 +0,0 @@ -*Wow, no problems at all. :)* \ No newline at end of file diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/notes.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/notes.md deleted file mode 100644 index d839d4c4..00000000 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/notes.md +++ /dev/null @@ -1,45 +0,0 @@ -# Notes - -## Setup - -```r -> options(Ncpus = 6L) -> install.packages("remotes") -> remotes::install_github("r-lib/revdepcheck") -``` - -```sh -## Used by R itself -$ revdep/run.R --preinstall RCurl XML -``` - - -## Pre-installation - -In order to run these checks successfully on a machine _without internet -access_, make sure to first populate the 'crancache' cache by pre-installing -all packages to be tested plus a few more. - -```sh -$ scl enable devtoolset-4 "revdep/run.R --preinstall blavaan" - -## All packages to be tested -$ revdep/run.R --preinstall-children -``` - - -## Testing - -### Package that requires Internet - -The following packages will fail when tested in 'offline' mode because -their examples or tests require a working internet connection: - -* BatchGetSymbols -* datapackage.r -* GetBCBData -* GSODR -* hackeRnews -* iml -* tableschema.r -* tsfeatures diff --git a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/problems.md b/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/problems.md deleted file mode 100644 index d67aa6ca..00000000 --- a/revdep/R_FUTURE_DEPRECATED_DEFUNCT=remote,transparent/problems.md +++ /dev/null @@ -1,3322 +0,0 @@ -# AIPW - -
- -* Version: 0.6.3.2 -* GitHub: https://github.com/yqzhong7/AIPW -* Source code: https://github.com/cran/AIPW -* Date/Publication: 2021-06-11 09:30:02 UTC -* Number of recursive dependencies: 99 - -Run `revdep_details(, "AIPW")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘Rsolnp’ ‘SuperLearner’ ‘future.apply’ ‘ggplot2’ ‘progressr’ ‘stats’ - ‘utils’ - All declared Imports should be used. - ``` - -# AlpsNMR - -
- -* Version: 3.4.0 -* GitHub: NA -* Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 169 - -Run `revdep_details(, "AlpsNMR")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘zip’ - All declared Imports should be used. - ``` - -# aroma.core - -
- -* Version: 3.2.2 -* GitHub: https://github.com/HenrikBengtsson/aroma.core -* Source code: https://github.com/cran/aroma.core -* Date/Publication: 2021-01-05 05:10:12 UTC -* Number of recursive dependencies: 48 - -Run `revdep_details(, "aroma.core")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Packages suggested but not available for checking: - 'sfit', 'expectile', 'HaarSeg', 'mpcbs' - ``` - -# BAMBI - -
- -* Version: 2.3.3 -* GitHub: https://github.com/c7rishi/BAMBI -* Source code: https://github.com/cran/BAMBI -* Date/Publication: 2021-10-02 13:40:23 UTC -* Number of recursive dependencies: 49 - -Run `revdep_details(, "BAMBI")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.3Mb - sub-directories of 1Mb or more: - libs 5.8Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘stats4’ - All declared Imports should be used. - ``` - -# baseballr - -
- -* Version: 1.2.0 -* GitHub: https://github.com/BillPetti/baseballr -* Source code: https://github.com/cran/baseballr -* Date/Publication: 2022-04-25 07:20:12 UTC -* Number of recursive dependencies: 122 - -Run `revdep_details(, "baseballr")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘pitchRx’ ‘progressr’ - All declared Imports should be used. - ``` - -# BatchGetSymbols - -
- -* Version: 2.6.1 -* GitHub: NA -* Source code: https://github.com/cran/BatchGetSymbols -* Date/Publication: 2020-11-28 15:10:21 UTC -* Number of recursive dependencies: 89 - -Run `revdep_details(, "BatchGetSymbols")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# bcmaps - -
- -* Version: 1.0.2 -* GitHub: https://github.com/bcgov/bcmaps -* Source code: https://github.com/cran/bcmaps -* Date/Publication: 2021-03-09 23:40:03 UTC -* Number of recursive dependencies: 129 - -Run `revdep_details(, "bcmaps")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# BEKKs - -
- -* Version: 1.1.0 -* GitHub: NA -* Source code: https://github.com/cran/BEKKs -* Date/Publication: 2022-03-19 00:20:02 UTC -* Number of recursive dependencies: 81 - -Run `revdep_details(, "BEKKs")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 14.7Mb - sub-directories of 1Mb or more: - libs 13.9Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘expm’ ‘forecast’ ‘parallel’ - All declared Imports should be used. - ``` - -# bigDM - -
- -* Version: 0.4.1 -* GitHub: https://github.com/spatialstatisticsupna/bigDM -* Source code: https://github.com/cran/bigDM -* Date/Publication: 2022-02-08 15:40:10 UTC -* Number of recursive dependencies: 125 - -Run `revdep_details(, "bigDM")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘INLA’ - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 940 marked Latin-1 strings - ``` - -# bistablehistory - -
- -* Version: 1.1.1 -* GitHub: https://github.com/alexander-pastukhov/bistablehistory -* Source code: https://github.com/cran/bistablehistory -* Date/Publication: 2022-03-22 13:40:02 UTC -* Number of recursive dependencies: 89 - -Run `revdep_details(, "bistablehistory")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 43.3Mb - sub-directories of 1Mb or more: - libs 42.4Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘RcppParallel’ ‘magrittr’ - All declared Imports should be used. - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# blavaan - -
- -* Version: 0.4-1 -* GitHub: NA -* Source code: https://github.com/cran/blavaan -* Date/Publication: 2022-01-27 21:40:02 UTC -* Number of recursive dependencies: 104 - -Run `revdep_details(, "blavaan")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 71.5Mb - sub-directories of 1Mb or more: - libs 68.9Mb - testdata 1.5Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# blockCV - -
- -* Version: 2.1.4 -* GitHub: https://github.com/rvalavi/blockCV -* Source code: https://github.com/cran/blockCV -* Date/Publication: 2021-06-17 04:50:02 UTC -* Number of recursive dependencies: 119 - -Run `revdep_details(, "blockCV")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.6Mb - sub-directories of 1Mb or more: - extdata 7.7Mb - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘biomod2’ - ``` - -# brms - -
- -* Version: 2.17.0 -* GitHub: https://github.com/paul-buerkner/brms -* Source code: https://github.com/cran/brms -* Date/Publication: 2022-04-13 14:22:29 UTC -* Number of recursive dependencies: 178 - -Run `revdep_details(, "brms")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘cmdstanr’ - ``` - -* checking installed package size ... NOTE - ``` - installed size is 8.7Mb - sub-directories of 1Mb or more: - R 4.2Mb - doc 3.6Mb - ``` - -# cfbfastR - -
- -* Version: 1.6.4 -* GitHub: https://github.com/saiemgilani/cfbfastR -* Source code: https://github.com/cran/cfbfastR -* Date/Publication: 2021-10-27 12:30:02 UTC -* Number of recursive dependencies: 110 - -Run `revdep_details(, "cfbfastR")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘xgboost’ - All declared Imports should be used. - ``` - -# ChromSCape - -
- -* Version: 1.4.0 -* GitHub: https://github.com/vallotlab/ChromSCape -* Source code: https://github.com/cran/ChromSCape -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 272 - -Run `revdep_details(, "ChromSCape")` for more info - -
- -## In both - -* checking for hidden files and directories ... NOTE - ``` - Found the following hidden files and directories: - .BBSoptions - These were most likely included in error. See section ‘Package - structure’ in the ‘Writing R Extensions’ manual. - ``` - -* checking installed package size ... NOTE - ``` - installed size is 7.9Mb - sub-directories of 1Mb or more: - data 1.3Mb - doc 2.9Mb - www 2.0Mb - ``` - -* checking R code for possible problems ... NOTE - ``` - CompareWilcox: no visible binding for global variable ‘annot.’ - bams_to_matrix_indexes: no visible binding for global variable - ‘files_dir_list’ - filter_correlated_cell_scExp: no visible binding for global variable - ‘run_tsne’ - generate_analysis: no visible binding for global variable ‘k’ - generate_analysis: no visible binding for global variable - ‘clusterConsensus’ - get_most_variable_cyto: no visible binding for global variable - ‘cytoBand’ - ... - plot_reduced_dim_scExp: no visible binding for global variable ‘V1’ - plot_reduced_dim_scExp: no visible binding for global variable ‘V2’ - plot_reduced_dim_scExp: no visible binding for global variable - ‘cluster’ - subset_bam_call_peaks: no visible binding for global variable - ‘merged_bam’ - Undefined global functions or variables: - Fri_cyto Gain_or_Loss V1 V2 absolute_value annot. cluster - clusterConsensus cytoBand files_dir_list genes k merged_bam ncells - run_tsne sample_id total_counts - ``` - -* checking Rd files ... NOTE - ``` - prepare_Rd: raw_counts_to_sparse_matrix.Rd:6-8: Dropping empty section \source - ``` - -* checking files in ‘vignettes’ ... NOTE - ``` - Files named as vignettes but with no recognized vignette engine: - ‘vignettes/PairedTag_Zhu_H3K4me1.Rmd’ - ‘vignettes/scChIC_Ku_H3K4me3.Rmd’ - (Is a VignetteBuilder field missing?) - ``` - -# civis - -
- -* Version: 3.0.0 -* GitHub: https://github.com/civisanalytics/civis-r -* Source code: https://github.com/cran/civis -* Date/Publication: 2020-06-22 18:00:02 UTC -* Number of recursive dependencies: 88 - -Run `revdep_details(, "civis")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# codebook - -
- -* Version: 0.9.2 -* GitHub: https://github.com/rubenarslan/codebook -* Source code: https://github.com/cran/codebook -* Date/Publication: 2020-06-06 23:40:03 UTC -* Number of recursive dependencies: 154 - -Run `revdep_details(, "codebook")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘userfriendlyscience’ - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘graphics’ ‘jsonlite’ ‘rlang’ ‘tidyselect’ ‘vctrs’ - All declared Imports should be used. - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 65 marked UTF-8 strings - ``` - -# cSEM - -
- -* Version: 0.4.0 -* GitHub: https://github.com/M-E-Rademaker/cSEM -* Source code: https://github.com/cran/cSEM -* Date/Publication: 2021-04-19 22:00:18 UTC -* Number of recursive dependencies: 122 - -Run `revdep_details(, "cSEM")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘Rdpack’ - All declared Imports should be used. - ``` - -# CSGo - -
- -* Version: 0.6.7 -* GitHub: https://github.com/adsoncostanzifilho/CSGo -* Source code: https://github.com/cran/CSGo -* Date/Publication: 2021-05-07 18:50:02 UTC -* Number of recursive dependencies: 74 - -Run `revdep_details(, "CSGo")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘extrafont’ ‘future’ - All declared Imports should be used. - ``` - -# datapackage.r - -
- -* Version: 1.3.5 -* GitHub: https://github.com/frictionlessdata/datapackage-r -* Source code: https://github.com/cran/datapackage.r -* Date/Publication: 2022-01-11 10:22:47 UTC -* Number of recursive dependencies: 118 - -Run `revdep_details(, "datapackage.r")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - ── Failure (test-profile.R:106:5): profile tabular-data-package should be up-to-date ── - profile$jsonschema not equal to `response.data`. - Component "properties": Component "licenses": Component "items": Names: 2 string mismatches - Component "properties": Component "licenses": Component "items": Length mismatch: comparison on first 5 components - Component "properties": Component "licenses": Component "items": Component 4: names for target but not for current - Component "properties": Component "licenses": Component "items": Component 4: Length mismatch: comparison on first 2 components - ... - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 4: Component 1: 1 string mismatch - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 4: Component 2: Modes: list, character - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 4: Component 2: Component 1: 1 string mismatch - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 5: Names: 1 string mismatch - Component "properties": Component "schema": Component "properties": Component "fields": Component "items": Component "anyOf": Component 1: Component 5: Component 5: Length mismatch: comparison on first 2 components - ... - - [ FAIL 5 | WARN 0 | SKIP 0 | PASS 248 ] - Error: Test failures - Execution halted - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘future’ ‘iterators’ ‘readr’ - All declared Imports should be used. - ``` - -# delayed - -
- -* Version: 0.3.0 -* GitHub: https://github.com/tlverse/delayed -* Source code: https://github.com/cran/delayed -* Date/Publication: 2020-02-28 11:40:02 UTC -* Number of recursive dependencies: 78 - -Run `revdep_details(, "delayed")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘assertthat’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# dipsaus - -
- -* Version: 0.2.0 -* GitHub: https://github.com/dipterix/dipsaus -* Source code: https://github.com/cran/dipsaus -* Date/Publication: 2022-01-27 17:30:02 UTC -* Number of recursive dependencies: 76 - -Run `revdep_details(, "dipsaus")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.9Mb - sub-directories of 1Mb or more: - doc 1.3Mb - libs 3.5Mb - ``` - -# dispositionEffect - -
- -* Version: 1.0.0 -* GitHub: https://github.com/marcozanotti/dispositionEffect -* Source code: https://github.com/cran/dispositionEffect -* Date/Publication: 2021-08-02 07:50:02 UTC -* Number of recursive dependencies: 120 - -Run `revdep_details(, "dispositionEffect")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - ── Failure (test-realized_duration.R:113:2): realized_duration works (realized_only = TRUE) ── - realized_duration(...) not equal to c(...). - 1/4 mismatches - [2] 34 - 28 == 6 - ── Failure (test-realized_duration.R:116:2): realized_duration works (realized_only = TRUE) ── - realized_duration(...) not equal to c(...). - ... - 1/4 mismatches - [2] 34 - 28 == 6 - ── Failure (test-realized_duration.R:161:2): realized_duration works (realized_only = TRUE) ── - realized_duration(...) not equal to c(...). - 1/4 mismatches - [1] 34 - 28 == 6 - - [ FAIL 36 | WARN 0 | SKIP 0 | PASS 331 ] - Error: Test failures - Execution halted - ``` - -# dragon - -
- -* Version: 1.2.1 -* GitHub: https://github.com/sjspielman/dragon -* Source code: https://github.com/cran/dragon -* Date/Publication: 2022-04-08 08:42:33 UTC -* Number of recursive dependencies: 135 - -Run `revdep_details(, "dragon")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘htmltools’ - All declared Imports should be used. - ``` - -# easyalluvial - -
- -* Version: 0.3.0 -* GitHub: https://github.com/erblast/easyalluvial -* Source code: https://github.com/cran/easyalluvial -* Date/Publication: 2021-01-13 10:40:09 UTC -* Number of recursive dependencies: 146 - -Run `revdep_details(, "easyalluvial")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘progress’ - All declared Imports should be used. - ``` - -# EFAtools - -
- -* Version: 0.4.1 -* GitHub: https://github.com/mdsteiner/EFAtools -* Source code: https://github.com/cran/EFAtools -* Date/Publication: 2022-04-24 14:40:02 UTC -* Number of recursive dependencies: 90 - -Run `revdep_details(, "EFAtools")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.7Mb - sub-directories of 1Mb or more: - libs 5.5Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘progress’ - All declared Imports should be used. - ``` - -# envi - -
- -* Version: 0.1.13 -* GitHub: https://github.com/Waller-SUSAN/envi -* Source code: https://github.com/cran/envi -* Date/Publication: 2022-03-24 08:40:17 UTC -* Number of recursive dependencies: 124 - -Run `revdep_details(, "envi")` for more info - -
- -## In both - -* checking whether package ‘envi’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: no DISPLAY variable so Tk is not available - See ‘/c4/home/henrik/repositories/future/revdep/checks/envi/new/envi.Rcheck/00install.out’ for details. - ``` - -# EpiNow2 - -
- -* Version: 1.3.2 -* GitHub: https://github.com/epiforecasts/EpiNow2 -* Source code: https://github.com/cran/EpiNow2 -* Date/Publication: 2020-12-14 09:00:15 UTC -* Number of recursive dependencies: 157 - -Run `revdep_details(, "EpiNow2")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘EpiSoon’ - ``` - -* checking installed package size ... NOTE - ``` - installed size is 168.1Mb - sub-directories of 1Mb or more: - libs 166.5Mb - ``` - -# epitweetr - -
- -* Version: 2.0.3 -* GitHub: https://github.com/EU-ECDC/epitweetr -* Source code: https://github.com/cran/epitweetr -* Date/Publication: 2022-01-05 10:00:08 UTC -* Number of recursive dependencies: 143 - -Run `revdep_details(, "epitweetr")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘taskscheduleR’ - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.1Mb - sub-directories of 1Mb or more: - doc 3.0Mb - java 1.3Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘httpuv’ ‘knitr’ ‘plyr’ ‘tidyverse’ ‘tokenizers’ ‘xml2’ - All declared Imports should be used. - ``` - -# fipe - -
- -* Version: 0.0.1 -* GitHub: https://github.com/italocegatta/fipe -* Source code: https://github.com/cran/fipe -* Date/Publication: 2019-08-25 07:20:06 UTC -* Number of recursive dependencies: 66 - -Run `revdep_details(, "fipe")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# flowGraph - -
- -* Version: 1.2.0 -* GitHub: https://github.com/aya49/flowGraph -* Source code: https://github.com/cran/flowGraph -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 87 - -Run `revdep_details(, "flowGraph")` for more info - -
- -## In both - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘flowGraph.Rmd’ using rmarkdown - - 8 pops @ layer 1 - 01:58:00-01:58:00 > 16:00:00 - - 24 pops @ layer 2 - 01:58:00-01:58:00 > 16:00:00 - - 32 pops @ layer 3 - 01:58:00-01:58:00 > 16:00:00 - - 16 pops @ layer 4 - 01:58:00-01:58:00 > 16:00:00 - ... - Quitting from lines 557-561 (flowGraph.Rmd) - Error: processing vignette 'flowGraph.Rmd' failed with diagnostics: - `map_df()` requires dplyr - --- failed re-building ‘flowGraph.Rmd’ - - SUMMARY: processing the following file failed: - ‘flowGraph.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -* checking R code for possible problems ... NOTE - ``` - get_child: no visible binding for global variable ‘no_cores’ - get_paren: no visible binding for global variable ‘no_cores’ - ms_psig: no visible binding for global variable ‘meta’ - Undefined global functions or variables: - meta no_cores - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘doParallel’ - ``` - -# foieGras - -
- -* Version: 0.7-6 -* GitHub: https://github.com/ianjonsen/foieGras -* Source code: https://github.com/cran/foieGras -* Date/Publication: 2021-04-26 22:10:07 UTC -* Number of recursive dependencies: 139 - -Run `revdep_details(, "foieGras")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 40.9Mb - sub-directories of 1Mb or more: - libs 40.0Mb - ``` - -# forecastML - -
- -* Version: 0.9.0 -* GitHub: https://github.com/nredell/forecastML -* Source code: https://github.com/cran/forecastML -* Date/Publication: 2020-05-07 15:10:17 UTC -* Number of recursive dependencies: 100 - -Run `revdep_details(, "forecastML")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘dtplyr’ - All declared Imports should be used. - ``` - -# geocmeans - -
- -* Version: 0.2.0 -* GitHub: https://github.com/JeremyGelb/geocmeans -* Source code: https://github.com/cran/geocmeans -* Date/Publication: 2021-08-23 07:11:35 UTC -* Number of recursive dependencies: 204 - -Run `revdep_details(, "geocmeans")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.4Mb - sub-directories of 1Mb or more: - data 2.3Mb - doc 1.9Mb - libs 6.1Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘rgdal’ - All declared Imports should be used. - ``` - -# GetBCBData - -
- -* Version: 0.6 -* GitHub: https://github.com/msperlin/GetBCBData -* Source code: https://github.com/cran/GetBCBData -* Date/Publication: 2021-01-21 17:40:07 UTC -* Number of recursive dependencies: 88 - -Run `revdep_details(, "GetBCBData")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘RCurl’ ‘lubridate’ ‘readr’ ‘stats’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# googleComputeEngineR - -
- -* Version: 0.3.0 -* GitHub: https://github.com/cloudyr/googleComputeEngineR -* Source code: https://github.com/cran/googleComputeEngineR -* Date/Publication: 2019-05-04 22:40:02 UTC -* Number of recursive dependencies: 68 - -Run `revdep_details(, "googleComputeEngineR")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# googleTagManageR - -
- -* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/googleTagManageR -* Date/Publication: 2022-04-16 18:12:29 UTC -* Number of recursive dependencies: 70 - -Run `revdep_details(, "googleTagManageR")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘assertthat’ ‘future’ ‘httr’ - All declared Imports should be used. - ``` - -# grattan - -
- -* Version: 1.9.0.10 -* GitHub: https://github.com/HughParsonage/grattan -* Source code: https://github.com/cran/grattan -* Date/Publication: 2022-01-10 01:02:41 UTC -* Number of recursive dependencies: 121 - -Run `revdep_details(, "grattan")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Packages suggested but not available for checking: - 'taxstats', 'taxstats1516' - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.1Mb - sub-directories of 1Mb or more: - libs 4.1Mb - ``` - -# greed - -
- -* Version: 0.6.0 -* GitHub: https://github.com/comeetie/greed -* Source code: https://github.com/cran/greed -* Date/Publication: 2022-03-18 12:50:02 UTC -* Number of recursive dependencies: 93 - -Run `revdep_details(, "greed")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 28.3Mb - sub-directories of 1Mb or more: - libs 26.0Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 989 marked UTF-8 strings - ``` - -# gWQS - -
- -* Version: 3.0.4 -* GitHub: NA -* Source code: https://github.com/cran/gWQS -* Date/Publication: 2021-05-20 09:30:02 UTC -* Number of recursive dependencies: 102 - -Run `revdep_details(, "gWQS")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘dplyr’ - All declared Imports should be used. - ``` - -# hackeRnews - -
- -* Version: 0.1.0 -* GitHub: https://github.com/szymanskir/hackeRnews -* Source code: https://github.com/cran/hackeRnews -* Date/Publication: 2019-12-13 13:20:05 UTC -* Number of recursive dependencies: 68 - -Run `revdep_details(, "hackeRnews")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# hal9001 - -
- -* Version: 0.4.3 -* GitHub: https://github.com/tlverse/hal9001 -* Source code: https://github.com/cran/hal9001 -* Date/Publication: 2022-02-09 22:50:02 UTC -* Number of recursive dependencies: 96 - -Run `revdep_details(, "hal9001")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.1Mb - sub-directories of 1Mb or more: - libs 5.7Mb - ``` - -# hwep - -
- -* Version: 0.0.1 -* GitHub: NA -* Source code: https://github.com/cran/hwep -* Date/Publication: 2021-09-28 10:30:02 UTC -* Number of recursive dependencies: 69 - -Run `revdep_details(, "hwep")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘future’ - All declared Imports should be used. - ``` - -# iml - -
- -* Version: 0.10.1 -* GitHub: https://github.com/christophM/iml -* Source code: https://github.com/cran/iml -* Date/Publication: 2020-09-24 12:30:14 UTC -* Number of recursive dependencies: 168 - -Run `revdep_details(, "iml")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘keras’ - All declared Imports should be used. - ``` - -# infercnv - -
- -* Version: 1.10.1 -* GitHub: https://github.com/broadinstitute/inferCNV -* Source code: https://github.com/cran/infercnv -* Date/Publication: 2021-11-08 -* Number of recursive dependencies: 135 - -Run `revdep_details(, "infercnv")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.0Mb - sub-directories of 1Mb or more: - extdata 3.1Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Unexported object imported by a ':::' call: ‘HiddenMarkov:::makedensity’ - See the note in ?`:::` about the use of this operator. - ``` - -# inlinedocs - -
- -* Version: 2019.12.5 -* GitHub: https://github.com/tdhock/inlinedocs -* Source code: https://github.com/cran/inlinedocs -* Date/Publication: 2019-12-05 23:30:07 UTC -* Number of recursive dependencies: 7 - -Run `revdep_details(, "inlinedocs")` for more info - -
- -## In both - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘R.methodsS3’ - ``` - -# ipc - -
- -* Version: 0.1.3 -* GitHub: https://github.com/fellstat/ipc -* Source code: https://github.com/cran/ipc -* Date/Publication: 2019-06-23 06:00:03 UTC -* Number of recursive dependencies: 69 - -Run `revdep_details(, "ipc")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ivmte - -
- -* Version: 1.4.0 -* GitHub: NA -* Source code: https://github.com/cran/ivmte -* Date/Publication: 2021-09-17 12:20:07 UTC -* Number of recursive dependencies: 111 - -Run `revdep_details(, "ivmte")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Packages suggested but not available for checking: 'gurobi', 'cplexAPI' - ``` - -# kernelboot - -
- -* Version: 0.1.7 -* GitHub: https://github.com/twolodzko/kernelboot -* Source code: https://github.com/cran/kernelboot -* Date/Publication: 2020-02-13 23:10:03 UTC -* Number of recursive dependencies: 64 - -Run `revdep_details(, "kernelboot")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# keyATM - -
- -* Version: 0.4.0 -* GitHub: https://github.com/keyATM/keyATM -* Source code: https://github.com/cran/keyATM -* Date/Publication: 2021-02-14 17:40:02 UTC -* Number of recursive dependencies: 107 - -Run `revdep_details(, "keyATM")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 18.9Mb - sub-directories of 1Mb or more: - libs 18.5Mb - ``` - -# lava - -
- -* Version: 1.6.10 -* GitHub: https://github.com/kkholst/lava -* Source code: https://github.com/cran/lava -* Date/Publication: 2021-09-02 14:50:18 UTC -* Number of recursive dependencies: 131 - -Run `revdep_details(, "lava")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Packages suggested but not available for checking: 'gof', 'lava.tobit' - ``` - -# lidR - -
- -* Version: 4.0.0 -* GitHub: https://github.com/r-lidar/lidR -* Source code: https://github.com/cran/lidR -* Date/Publication: 2022-02-18 16:10:03 UTC -* Number of recursive dependencies: 158 - -Run `revdep_details(, "lidR")` for more info - -
- -## In both - -* checking examples ... ERROR - ``` - Running examples in ‘lidR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: its_dalponte2016 - > ### Title: Individual Tree Segmentation Algorithm - > ### Aliases: its_dalponte2016 dalponte2016 - > - > ### ** Examples - > - > LASfile <- system.file("extdata", "MixedConifer.laz", package="lidR") - ... - > chm <- rasterize_canopy(las, 0.5, p2r(0.3), pkg = "raster") - > ker <- matrix(1,3,3) - > chm <- raster::focal(chm, w = ker, fun = mean, na.rm = TRUE) - > - > ttops <- locate_trees(chm, lmf(4, 2)) - > las <- segment_trees(las, dalponte2016(chm, ttops)) - Error in geos_op2_geom("intersection", x, y, ...) : - st_crs(x) == st_crs(y) is not TRUE - Calls: segment_trees ... st_intersection.sf -> geos_op2_df -> geos_op2_geom -> stopifnot - Execution halted - ``` - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - 3. └─lidR algorithm(st_bbox(las)) - 4. └─lidR:::crop_special_its(treetops, chm, bbox) - 5. └─lidR:::raster_crop(chm, bbox) - 6. ├─sf::st_crop(raster, bbox) - 7. └─stars:::st_crop.stars(raster, bbox) - ── Error (test-segment_trees.R:147:3): Silva algorithm works with sfc ────────── - ... - 7. └─lidR:::segment_trees.LAS(las, silva2016(chm, ttops_shifted500)) - 8. └─lidR algorithm(st_bbox(las)) - 9. └─lidR:::crop_special_its(treetops, chm, bbox) - 10. └─lidR:::raster_crop(chm, bbox) - 11. ├─sf::st_crop(raster, bbox) - 12. └─stars:::st_crop.stars(raster, bbox) - - [ FAIL 20 | WARN 5 | SKIP 40 | PASS 1345 ] - Error: Test failures - Execution halted - ``` - -* checking installed package size ... NOTE - ``` - installed size is 15.8Mb - sub-directories of 1Mb or more: - R 1.1Mb - doc 1.0Mb - extdata 1.1Mb - libs 12.0Mb - ``` - -# lmtp - -
- -* Version: 1.0.0 -* GitHub: https://github.com/nt-williams/lmtp -* Source code: https://github.com/cran/lmtp -* Date/Publication: 2021-09-29 07:10:07 UTC -* Number of recursive dependencies: 113 - -Run `revdep_details(, "lmtp")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘R6’ ‘nnls’ ‘utils’ - All declared Imports should be used. - ``` - -# MAI - -
- -* Version: 1.0.0 -* GitHub: https://github.com/KechrisLab/MAI -* Source code: https://github.com/cran/MAI -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 164 - -Run `revdep_details(, "MAI")` for more info - -
- -## In both - -* checking top-level files ... NOTE - ``` - File - LICENSE - is not mentioned in the DESCRIPTION file. - ``` - -# microservices - -
- -* Version: 0.1.2 -* GitHub: https://github.com/tidylab/microservices -* Source code: https://github.com/cran/microservices -* Date/Publication: 2021-06-12 06:10:02 UTC -* Number of recursive dependencies: 69 - -Run `revdep_details(, "microservices")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(microservices) - > test_check("microservices") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 12 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - Backtrace: - ▆ - 1. ├─config::get(...) at test-endpoint-plumber-{route_name}.R:2:0 - 2. │ └─base::normalizePath(file, mustWork = FALSE) - 3. │ └─base::path.expand(path) - 4. └─base::system.file(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 12 ] - Error: Test failures - Execution halted - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘config’ ‘desc’ ‘dplyr’ ‘glue’ ‘withr’ - All declared Imports should be used. - ``` - -# MineICA - -
- -* Version: 1.34.0 -* GitHub: NA -* Source code: https://github.com/cran/MineICA -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 208 - -Run `revdep_details(, "MineICA")` for more info - -
- -## In both - -* checking Rd cross-references ... WARNING - ``` - Missing link or links in documentation object 'Alist.Rd': - ‘class-IcaSet’ - - Missing link or links in documentation object 'Slist.Rd': - ‘class-IcaSet’ - - Missing link or links in documentation object 'class-IcaSet.Rd': - ‘class-IcaSet’ - - Missing link or links in documentation object 'getComp.Rd': - ‘class-IcaSet’ - - Missing link or links in documentation object 'runAn.Rd': - ‘[Category:class-GOHyperGParams]{GOHyperGParams}’ - - See section 'Cross-references' in the 'Writing R Extensions' manual. - ``` - -* checking for missing documentation entries ... WARNING - ``` - Undocumented S4 classes: - ‘MineICAParams’ - All user-level objects in a package (including S4 classes and methods) - should have documentation entries. - See chapter ‘Writing R documentation files’ in the ‘Writing R - Extensions’ manual. - ``` - -* checking package dependencies ... NOTE - ``` - Package which this enhances but not available for checking: ‘doMC’ - - Depends: includes the non-default packages: - 'BiocGenerics', 'Biobase', 'plyr', 'ggplot2', 'scales', 'foreach', - 'xtable', 'biomaRt', 'gtools', 'GOstats', 'cluster', 'marray', - 'mclust', 'RColorBrewer', 'colorspace', 'igraph', 'Rgraphviz', - 'graph', 'annotate', 'Hmisc', 'fastICA', 'JADE' - Adding so many packages to the search path is excessive and importing - selectively is preferable. - ``` - -* checking DESCRIPTION meta-information ... NOTE - ``` - Packages listed in more than one of Depends, Imports, Suggests, Enhances: - ‘biomaRt’ ‘GOstats’ ‘cluster’ ‘mclust’ ‘igraph’ - A package should be listed in only one of these fields. - ``` - -* checking dependencies in R code ... NOTE - ``` - 'library' or 'require' call to ‘GOstats’ which was already attached by Depends. - Please remove these calls from your code. - Namespace in Imports field not imported from: ‘lumiHumanAll.db’ - All declared Imports should be used. - Packages in Depends field not imported from: - ‘GOstats’ ‘Hmisc’ ‘JADE’ ‘RColorBrewer’ ‘Rgraphviz’ ‘annotate’ - ‘biomaRt’ ‘cluster’ ‘colorspace’ ‘fastICA’ ‘foreach’ ‘ggplot2’ - ‘graph’ ‘gtools’ ‘igraph’ ‘marray’ ‘mclust’ ‘methods’ ‘plyr’ ‘scales’ - ‘xtable’ - These packages need to be imported from (in the NAMESPACE file) - for when this namespace is loaded but not attached. - ':::' calls which should be '::': - ‘Biobase:::annotation<-’ ‘Biobase:::validMsg’ ‘fpc:::pamk’ - ‘lumi:::getChipInfo’ ‘mclust:::adjustedRandIndex’ - See the note in ?`:::` about the use of this operator. - Unexported object imported by a ':::' call: ‘Biobase:::isValidVersion’ - See the note in ?`:::` about the use of this operator. - ``` - -* checking R code for possible problems ... NOTE - ``` - addGenesToGoReport: no visible global function definition for - ‘geneIdsByCategory’ - addGenesToGoReport: no visible global function definition for - ‘geneIdUniverse’ - addGenesToGoReport: no visible global function definition for - ‘conditional’ - addGenesToGoReport: no visible global function definition for - ‘sigCategories’ - annot2Color: no visible global function definition for ‘brewer.pal’ - annot2Color: no visible global function definition for ‘heat_hcl’ - ... - importFrom("methods", "callNextMethod", "new", "validObject") - importFrom("stats", "aggregate", "as.dendrogram", "as.dist", - "as.hclust", "chisq.test", "cor", "cor.test", "cutree", - "dist", "hclust", "kmeans", "kruskal.test", "lm", "median", - "na.omit", "order.dendrogram", "p.adjust", "quantile", - "reorder", "shapiro.test", "wilcox.test") - importFrom("utils", "capture.output", "combn", "read.table", - "write.table") - to your NAMESPACE file (and ensure that your DESCRIPTION Imports field - contains 'methods'). - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘MineICA.Rnw’ using Sweave - Loading required package: BiocGenerics - - Attaching package: ‘BiocGenerics’ - - The following objects are masked from ‘package:stats’: - - IQR, mad, sd, var, xtabs - - ... - l.23 \usepackage - {subfig}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘MineICA.Rnw’ - - SUMMARY: processing the following file failed: - ‘MineICA.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# missSBM - -
- -* Version: 1.0.2 -* GitHub: https://github.com/grossSBM/missSBM -* Source code: https://github.com/cran/missSBM -* Date/Publication: 2022-02-01 16:00:20 UTC -* Number of recursive dependencies: 108 - -Run `revdep_details(, "missSBM")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.4Mb - sub-directories of 1Mb or more: - libs 6.5Mb - ``` - -# momentuHMM - -
- -* Version: 1.5.4 -* GitHub: https://github.com/bmcclintock/momentuHMM -* Source code: https://github.com/cran/momentuHMM -* Date/Publication: 2021-09-03 04:30:02 UTC -* Number of recursive dependencies: 195 - -Run `revdep_details(, "momentuHMM")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 9.1Mb - sub-directories of 1Mb or more: - R 1.2Mb - doc 1.7Mb - libs 5.6Mb - ``` - -# onemapsgapi - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/onemapsgapi -* Date/Publication: 2020-02-06 11:00:02 UTC -* Number of recursive dependencies: 66 - -Run `revdep_details(, "onemapsgapi")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# OOS - -
- -* Version: 1.0.0 -* GitHub: https://github.com/tylerJPike/OOS -* Source code: https://github.com/cran/OOS -* Date/Publication: 2021-03-17 13:20:20 UTC -* Number of recursive dependencies: 131 - -Run `revdep_details(, "OOS")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# partR2 - -
- -* Version: 0.9.1 -* GitHub: https://github.com/mastoffel/partR2 -* Source code: https://github.com/cran/partR2 -* Date/Publication: 2021-01-18 16:30:04 UTC -* Number of recursive dependencies: 91 - -Run `revdep_details(, "partR2")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘methods’ - All declared Imports should be used. - ``` - -# pavo - -
- -* Version: 2.7.1 -* GitHub: https://github.com/rmaia/pavo -* Source code: https://github.com/cran/pavo -* Date/Publication: 2021-09-21 13:10:21 UTC -* Number of recursive dependencies: 87 - -Run `revdep_details(, "pavo")` for more info - -
- -## In both - -* checking whether package ‘pavo’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: no DISPLAY variable so Tk is not available - See ‘/c4/home/henrik/repositories/future/revdep/checks/pavo/new/pavo.Rcheck/00install.out’ for details. - ``` - -# photosynthesis - -
- -* Version: 2.0.1 -* GitHub: https://github.com/cdmuir/photosynthesis -* Source code: https://github.com/cran/photosynthesis -* Date/Publication: 2021-07-01 04:30:02 UTC -* Number of recursive dependencies: 104 - -Run `revdep_details(, "photosynthesis")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - | - |=================================== | 50% - | - |======================================================================| 100%[ FAIL 6 | WARN 0 | SKIP 0 | PASS 149 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - `Wt1` not equal to `Wt2`. - Attributes: < Modes: list, NULL > - Attributes: < Lengths: 2, 0 > - Attributes: < names for target but not for current > - Attributes: < current is not list-like > - target is units, current is numeric - - [ FAIL 6 | WARN 0 | SKIP 0 | PASS 149 ] - Error: Test failures - Execution halted - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.1Mb - sub-directories of 1Mb or more: - doc 3.4Mb - help 1.1Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘future’ - All declared Imports should be used. - ``` - -# phylolm - -
- -* Version: 2.6.2 -* GitHub: https://github.com/lamho86/phylolm -* Source code: https://github.com/cran/phylolm -* Date/Publication: 2020-06-22 05:10:08 UTC -* Number of recursive dependencies: 41 - -Run `revdep_details(, "phylolm")` for more info - -
- -## In both - -* checking Rd cross-references ... NOTE - ``` - Packages unavailable to check Rd xrefs: ‘geiger’, ‘caper’ - ``` - -# PLNmodels - -
- -* Version: 0.11.6 -* GitHub: https://github.com/pln-team/PLNmodels -* Source code: https://github.com/cran/PLNmodels -* Date/Publication: 2022-02-01 16:00:24 UTC -* Number of recursive dependencies: 173 - -Run `revdep_details(, "PLNmodels")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 16.9Mb - sub-directories of 1Mb or more: - doc 2.0Mb - libs 13.8Mb - ``` - -# plumber - -
- -* Version: 1.1.0 -* GitHub: https://github.com/rstudio/plumber -* Source code: https://github.com/cran/plumber -* Date/Publication: 2021-03-24 05:10:02 UTC -* Number of recursive dependencies: 81 - -Run `revdep_details(, "plumber")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ppcseq - -
- -* Version: 1.2.0 -* GitHub: https://github.com/stemangiola/ppcseq -* Source code: https://github.com/cran/ppcseq -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 117 - -Run `revdep_details(, "ppcseq")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 45.6Mb - sub-directories of 1Mb or more: - data 1.5Mb - libs 42.8Mb - ``` - -* checking R code for possible problems ... NOTE - ``` - .identify_abundant: no visible binding for global variable ‘.’ - .identify_abundant: no visible binding for global variable ‘.abundant’ - add_exposure_rate: no visible binding for global variable ‘.variable’ - add_exposure_rate: no visible binding for global variable ‘S’ - add_exposure_rate: no visible binding for global variable ‘exposure - rate’ - add_partition: no visible binding for global variable ‘.’ - add_scaled_counts_bulk.calcNormFactor: no visible binding for global - variable ‘transcript’ - add_scaled_counts_bulk.get_low_expressed: no visible binding for global - ... - . .abundant .chain .draw .iteration .lower .upper .upper_2 .value - .variable CI G S TMM cc chains dummy exposure rate idx_MPI init l l - %>% sd med multiplier nf ppc read count MPI row res_discovery rowid s - sample wise data scale_abundance slope symbol MPI row tot tot_filt - transcript write_on_disk - Consider adding - importFrom("base", "row", "sample") - importFrom("stats", "sd") - importFrom("utils", "data") - to your NAMESPACE file. - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# ppseq - -
- -* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/ppseq -* Date/Publication: 2021-09-09 09:00:02 UTC -* Number of recursive dependencies: 100 - -Run `revdep_details(, "ppseq")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.3Mb - sub-directories of 1Mb or more: - doc 5.2Mb - ``` - -# prewas - -
- -* Version: 1.1.1 -* GitHub: https://github.com/Snitkin-Lab-Umich/prewas -* Source code: https://github.com/cran/prewas -* Date/Publication: 2021-04-02 12:20:05 UTC -* Number of recursive dependencies: 75 - -Run `revdep_details(, "prewas")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘stats’ - All declared Imports should be used. - ``` - -# promises - -
- -* Version: 1.2.0.1 -* GitHub: https://github.com/rstudio/promises -* Source code: https://github.com/cran/promises -* Date/Publication: 2021-02-11 19:00:02 UTC -* Number of recursive dependencies: 67 - -Run `revdep_details(, "promises")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# Prostar - -
- -* Version: 1.26.4 -* GitHub: https://github.com/samWieczorek/Prostar -* Source code: https://github.com/cran/Prostar -* Date/Publication: 2022-01-23 -* Number of recursive dependencies: 320 - -Run `revdep_details(, "Prostar")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘BiocManager’ ‘DAPAR’ ‘DAPARdata’ ‘DT’ ‘R.utils’ ‘XML’ ‘colourpicker’ - ‘data.table’ ‘future’ ‘highcharter’ ‘htmlwidgets’ ‘later’ ‘promises’ - ‘rclipboard’ ‘rhandsontable’ ‘sass’ ‘shinyAce’ ‘shinyBS’ ‘shinyTree’ - ‘shinyWidgets’ ‘shinycssloaders’ ‘shinyjqui’ ‘shinyjs’ ‘shinythemes’ - ‘tibble’ ‘webshot’ - All declared Imports should be used. - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Prostar_UserManual.Rnw’ using Sweave - Error: processing vignette 'Prostar_UserManual.Rnw' failed with diagnostics: - Running 'texi2dvi' on 'Prostar_UserManual.tex' failed. - LaTeX errors: - ! LaTeX Error: File `nowidow.sty' not found. - - Type X to quit or to proceed, - or enter new name. (Default extension: sty) - ... - l.189 \RequirePackage - {parnotes}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘Prostar_UserManual.Rnw’ - - SUMMARY: processing the following file failed: - ‘Prostar_UserManual.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# PUMP - -
- -* Version: 1.0.0 -* GitHub: https://github.com/MDRCNY/PUMP -* Source code: https://github.com/cran/PUMP -* Date/Publication: 2022-02-09 09:50:05 UTC -* Number of recursive dependencies: 129 - -Run `revdep_details(, "PUMP")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘here’ - All declared Imports should be used. - ``` - -# QDNAseq - -
- -* Version: 1.30.0 -* GitHub: https://github.com/ccagc/QDNAseq -* Source code: https://github.com/cran/QDNAseq -* Date/Publication: 2021-10-26 -* Number of recursive dependencies: 80 - -Run `revdep_details(, "QDNAseq")` for more info - -
- -## In both - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘QDNAseq.Rnw’ using Sweave - EM algorithm started ... - - Warning in allprior/tot : - Recycling array of length 1 in vector-array arithmetic is deprecated. - Use c() or as.vector() instead. - - Warning in allprior/tot : - Recycling array of length 1 in vector-array arithmetic is deprecated. - ... - l.189 \RequirePackage - {parnotes}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘QDNAseq.Rnw’ - - SUMMARY: processing the following file failed: - ‘QDNAseq.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# RAINBOWR - -
- -* Version: 0.1.29 -* GitHub: NA -* Source code: https://github.com/cran/RAINBOWR -* Date/Publication: 2022-01-07 13:53:11 UTC -* Number of recursive dependencies: 147 - -Run `revdep_details(, "RAINBOWR")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 32.6Mb - sub-directories of 1Mb or more: - libs 31.4Mb - ``` - -# regmedint - -
- -* Version: 1.0.0 -* GitHub: https://github.com/kaz-yos/regmedint -* Source code: https://github.com/cran/regmedint -* Date/Publication: 2022-04-06 20:20:02 UTC -* Number of recursive dependencies: 131 - -Run `revdep_details(, "regmedint")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘Deriv’ - All declared Imports should be used. - ``` - -# remiod - -
- -* Version: 1.0.0 -* GitHub: https://github.com/xsswang/remiod -* Source code: https://github.com/cran/remiod -* Date/Publication: 2022-03-14 08:50:02 UTC -* Number of recursive dependencies: 125 - -Run `revdep_details(, "remiod")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘reshape2’ - All declared Imports should be used. - ``` - -# rgee - -
- -* Version: 1.1.3 -* GitHub: https://github.com/r-spatial/rgee -* Source code: https://github.com/cran/rgee -* Date/Publication: 2022-03-16 15:50:02 UTC -* Number of recursive dependencies: 150 - -Run `revdep_details(, "rgee")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.2Mb - sub-directories of 1Mb or more: - doc 7.0Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘R6’ - All declared Imports should be used. - ``` - -# robotstxt - -
- -* Version: 0.7.13 -* GitHub: https://github.com/ropensci/robotstxt -* Source code: https://github.com/cran/robotstxt -* Date/Publication: 2020-09-03 19:30:02 UTC -* Number of recursive dependencies: 68 - -Run `revdep_details(, "robotstxt")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘future’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# sapfluxnetr - -
- -* Version: 0.1.3 -* GitHub: https://github.com/sapfluxnet/sapfluxnetr -* Source code: https://github.com/cran/sapfluxnetr -* Date/Publication: 2021-11-19 15:10:02 UTC -* Number of recursive dependencies: 78 - -Run `revdep_details(, "sapfluxnetr")` for more info - -
- -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 4 marked UTF-8 strings - ``` - -# scDiffCom - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/scDiffCom -* Date/Publication: 2021-08-17 07:20:05 UTC -* Number of recursive dependencies: 245 - -Run `revdep_details(, "scDiffCom")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘future’ ‘utils’ - All declared Imports should be used. - ``` - -# sctransform - -
- -* Version: 0.3.3 -* GitHub: https://github.com/satijalab/sctransform -* Source code: https://github.com/cran/sctransform -* Date/Publication: 2022-01-13 08:20:02 UTC -* Number of recursive dependencies: 69 - -Run `revdep_details(, "sctransform")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package which this enhances but not available for checking: ‘glmGamPoi’ - ``` - -# sdmApp - -
- -* Version: 0.0.2 -* GitHub: https://github.com/Abson-dev/sdmApp -* Source code: https://github.com/cran/sdmApp -* Date/Publication: 2021-07-07 08:30:02 UTC -* Number of recursive dependencies: 167 - -Run `revdep_details(, "sdmApp")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘sp’ - All declared Imports should be used. - ``` - -# seer - -
- -* Version: 1.1.7 -* GitHub: https://github.com/thiyangt/seer -* Source code: https://github.com/cran/seer -* Date/Publication: 2021-12-08 05:20:02 UTC -* Number of recursive dependencies: 115 - -Run `revdep_details(, "seer")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘MASS’ - All declared Imports should be used. - ``` - -# sentopics - -
- -* Version: 0.6.2 -* GitHub: https://github.com/odelmarcelle/sentopics -* Source code: https://github.com/cran/sentopics -* Date/Publication: 2022-03-15 13:50:02 UTC -* Number of recursive dependencies: 145 - -Run `revdep_details(, "sentopics")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 13.8Mb - sub-directories of 1Mb or more: - data 1.2Mb - doc 7.4Mb - libs 4.8Mb - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘lexicon’ - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 3128 marked UTF-8 strings - ``` - -# Seurat - -
- -* Version: 4.1.0 -* GitHub: https://github.com/satijalab/seurat -* Source code: https://github.com/cran/Seurat -* Date/Publication: 2022-01-14 18:32:42 UTC -* Number of recursive dependencies: 254 - -Run `revdep_details(, "Seurat")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 12.0Mb - sub-directories of 1Mb or more: - R 1.3Mb - libs 10.1Mb - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘Signac’ - ``` - -# shiny - -
- -* Version: 1.7.1 -* GitHub: https://github.com/rstudio/shiny -* Source code: https://github.com/cran/shiny -* Date/Publication: 2021-10-02 04:30:02 UTC -* Number of recursive dependencies: 105 - -Run `revdep_details(, "shiny")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 9.3Mb - sub-directories of 1Mb or more: - R 1.6Mb - www 6.6Mb - ``` - -# shiny.worker - -
- -* Version: 0.0.1 -* GitHub: NA -* Source code: https://github.com/cran/shiny.worker -* Date/Publication: 2021-01-21 11:00:02 UTC -* Number of recursive dependencies: 64 - -Run `revdep_details(, "shiny.worker")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘R6’ ‘shiny’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# shinyrecap - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/shinyrecap -* Date/Publication: 2019-01-19 23:40:03 UTC -* Number of recursive dependencies: 96 - -Run `revdep_details(, "shinyrecap")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘CARE1’ ‘LCMCR’ ‘coda’ ‘conting’ ‘dga’ ‘future’ ‘ggplot2’ ‘ipc’ - ‘promises’ ‘reshape’ ‘shinycssloaders’ ‘testthat’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# simhelpers - -
- -* Version: 0.1.1 -* GitHub: https://github.com/meghapsimatrix/simhelpers -* Source code: https://github.com/cran/simhelpers -* Date/Publication: 2021-02-14 17:50:02 UTC -* Number of recursive dependencies: 103 - -Run `revdep_details(, "simhelpers")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘future’ ‘magrittr’ ‘purrr’ ‘rlang’ ‘utils’ - All declared Imports should be used. - ``` - -# skpr - -
- -* Version: 1.1.4 -* GitHub: https://github.com/tylermorganwall/skpr -* Source code: https://github.com/cran/skpr -* Date/Publication: 2022-04-08 19:40:02 UTC -* Number of recursive dependencies: 125 - -Run `revdep_details(, "skpr")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 47.8Mb - sub-directories of 1Mb or more: - libs 46.3Mb - ``` - -# solitude - -
- -* Version: 1.1.3 -* GitHub: https://github.com/talegari/solitude -* Source code: https://github.com/cran/solitude -* Date/Publication: 2021-07-29 20:00:02 UTC -* Number of recursive dependencies: 125 - -Run `revdep_details(, "solitude")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘R6’ ‘lgr’ - All declared Imports should be used. - ``` - -# spacey - -
- -* Version: 0.1.1 -* GitHub: https://github.com/mikemahoney218/spacey -* Source code: https://github.com/cran/spacey -* Date/Publication: 2020-03-14 18:50:02 UTC -* Number of recursive dependencies: 88 - -Run `revdep_details(, "spacey")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘rgdal’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# SpaDES.core - -
- -* Version: 1.0.10 -* GitHub: https://github.com/PredictiveEcology/SpaDES.core -* Source code: https://github.com/cran/SpaDES.core -* Date/Publication: 2022-01-19 16:22:46 UTC -* Number of recursive dependencies: 152 - -Run `revdep_details(, "SpaDES.core")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘test-all.R’/software/c4/cbi/software/R-4.1.3-gcc8/lib64/R/bin/BATCH: line 60: 239437 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 - - ERROR - Running the tests in ‘tests/test-all.R’ failed. - Last 50 lines of output: - 2b0930661000-2b0930860000 ---p 00005000 00:27 8780240713555077915 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/fastmatch/libs/fastmatch.so - 2b0930860000-2b0930861000 r--p 00004000 00:27 8780240713555077915 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/fastmatch/libs/fastmatch.so - 2b0930861000-2b0930862000 rw-p 00005000 00:27 8780240713555077915 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/fastmatch/libs/fastmatch.so - 2b0930862000-2b0930881000 r-xp 00000000 00:27 7031816349168644086 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/SpaDES.tools/libs/SpaDES.tools.so - 2b0930881000-2b0930a81000 ---p 0001f000 00:27 7031816349168644086 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/SpaDES.tools/libs/SpaDES.tools.so - ... - 2b0932c95000-2b0932e95000 rw-p 00000000 00:00 0 - 2b0932e95000-2b0932e96000 ---p 00000000 00:00 0 - 2b0932e96000-2b0933096000 rw-p 00000000 00:00 0 - 2b0933096000-2b0933098000 r-xp 00000000 00:27 11903773676305457698 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 2b0933098000-2b0933297000 ---p 00002000 00:27 11903773676305457698 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 2b0933297000-2b0933298000 r--p 00001000 00:27 11903773676305457698 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 2b0933298000-2b0933299000 rw-p 00002000 00:27 11903773676305457698 /c4/home/henrik/repositories/future/revdep/library/SpaDES.core/xfun/libs/xfun.so - 7ffcf0fd0000-7ffcf1135000 rw-p 00000000 00:00 0 [stack] - 7ffcf1190000-7ffcf1192000 r-xp 00000000 00:00 0 [vdso] - ffffffffff600000-ffffffffff601000 r-xp 00000000 00:00 0 [vsyscall] - ``` - -# spaMM - -
- -* Version: 3.11.14 -* GitHub: NA -* Source code: https://github.com/cran/spaMM -* Date/Publication: 2022-04-09 23:30:02 UTC -* Number of recursive dependencies: 100 - -Run `revdep_details(, "spaMM")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Packages which this enhances but not available for checking: - 'multcomp', 'RLRsim' - ``` - -* checking installed package size ... NOTE - ``` - installed size is 46.9Mb - sub-directories of 1Mb or more: - R 2.2Mb - libs 43.6Mb - ``` - -# sparrpowR - -
- -* Version: 0.2.5 -* GitHub: https://github.com/machiela-lab/sparrpowR -* Source code: https://github.com/cran/sparrpowR -* Date/Publication: 2022-02-05 00:30:02 UTC -* Number of recursive dependencies: 98 - -Run `revdep_details(, "sparrpowR")` for more info - -
- -## In both - -* checking whether package ‘sparrpowR’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: no DISPLAY variable so Tk is not available - See ‘/c4/home/henrik/repositories/future/revdep/checks/sparrpowR/new/sparrpowR.Rcheck/00install.out’ for details. - ``` - -# SPARSEMODr - -
- -* Version: 1.1.0 -* GitHub: https://github.com/NAU-CCL/SPARSEMODr -* Source code: https://github.com/cran/SPARSEMODr -* Date/Publication: 2021-07-01 17:50:02 UTC -* Number of recursive dependencies: 119 - -Run `revdep_details(, "SPARSEMODr")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘future’ ‘geosphere’ ‘lubridate’ ‘tidyverse’ ‘viridis’ - All declared Imports should be used. - ``` - -# spatialTIME - -
- -* Version: 1.2.0 -* GitHub: https://github.com/FridleyLab/spatialTIME -* Source code: https://github.com/cran/spatialTIME -* Date/Publication: 2021-09-11 04:10:02 UTC -* Number of recursive dependencies: 120 - -Run `revdep_details(, "spatialTIME")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘ggpubr’ ‘pheatmap’ ‘rlist’ ‘stats’ ‘viridis’ - All declared Imports should be used. - ``` - -# spatialwarnings - -
- -* Version: 3.0.3 -* GitHub: https://github.com/spatial-ews/spatialwarnings -* Source code: https://github.com/cran/spatialwarnings -* Date/Publication: 2022-03-21 13:00:02 UTC -* Number of recursive dependencies: 84 - -Run `revdep_details(, "spatialwarnings")` for more info - -
- -## In both - -* checking Rd cross-references ... WARNING - ``` - Missing link or links in documentation object 'indictest.Rd': - ‘mgcv’ - - See section 'Cross-references' in the 'Writing R Extensions' manual. - ``` - -* checking installed package size ... NOTE - ``` - installed size is 6.4Mb - sub-directories of 1Mb or more: - libs 5.4Mb - ``` - -# sphunif - -
- -* Version: 1.0.1 -* GitHub: https://github.com/egarpor/sphunif -* Source code: https://github.com/cran/sphunif -* Date/Publication: 2021-09-02 07:40:02 UTC -* Number of recursive dependencies: 72 - -Run `revdep_details(, "sphunif")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 20.5Mb - sub-directories of 1Mb or more: - libs 19.6Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 189 marked UTF-8 strings - ``` - -# spNetwork - -
- -* Version: 0.4.3.1 -* GitHub: https://github.com/JeremyGelb/spNetwork -* Source code: https://github.com/cran/spNetwork -* Date/Publication: 2022-04-23 23:50:02 UTC -* Number of recursive dependencies: 148 - -Run `revdep_details(, "spNetwork")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 18.6Mb - sub-directories of 1Mb or more: - doc 1.1Mb - extdata 2.6Mb - libs 13.5Mb - ``` - -# ssdtools - -
- -* Version: 1.0.1 -* GitHub: https://github.com/bcgov/ssdtools -* Source code: https://github.com/cran/ssdtools -* Date/Publication: 2022-04-10 21:40:02 UTC -* Number of recursive dependencies: 141 - -Run `revdep_details(, "ssdtools")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 17.6Mb - sub-directories of 1Mb or more: - doc 1.2Mb - libs 15.1Mb - ``` - -# stars - -
- -* Version: 0.5-5 -* GitHub: https://github.com/r-spatial/stars -* Source code: https://github.com/cran/stars -* Date/Publication: 2021-12-19 03:20:02 UTC -* Number of recursive dependencies: 148 - -Run `revdep_details(, "stars")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘starsdata’ - ``` - -* checking installed package size ... NOTE - ``` - installed size is 8.6Mb - sub-directories of 1Mb or more: - doc 2.3Mb - nc 4.5Mb - ``` - -# synergyfinder - -
- -* Version: 3.2.10 -* GitHub: NA -* Source code: https://github.com/cran/synergyfinder -* Date/Publication: 2022-03-31 -* Number of recursive dependencies: 181 - -Run `revdep_details(, "synergyfinder")` for more info - -
- -## In both - -* checking dependencies in R code ... WARNING - ``` - '::' or ':::' import not declared from: ‘scales’ - Namespaces in Imports field not imported from: - ‘future’ ‘gstat’ ‘nleqslv’ ‘sp’ ‘tidyverse’ - All declared Imports should be used. - ``` - -* checking for code/documentation mismatches ... WARNING - ``` - Codoc mismatches from documentation object 'PlotDoseResponse': - PlotDoseResponse - Code: function(data, block_ids = c(1), drugs = c(1, 2), adjusted = - TRUE, statistic = NULL, summary_statistic = "mean", - high_value_color = "#FF0000", low_value_color = - "#00FF00", point_color = "#C24B40", curve_color = - "black", curve_ylim = NULL, curve_grid = TRUE, - text_size_scale = 1, heatmap_text_label_size_scale = - 1, heatmap_text_label_color = "#000000", - heatmap_color_range = NULL, curve_plot_title = NULL, - ... - high_value_color = "#A90217", low_value_color = - "#2166AC", text_size_scale = 1, - heatmap_text_label_size_scale = 1, - heatmap_text_label_color = "#000000", grid = TRUE, - dynamic = FALSE, display = TRUE, save_file = FALSE, - file_type = "pdf", file_name = NULL, file_path = NULL, - height = 6, width = 6, units = "in") - Mismatches in argument default values: - Name: 'high_value_color' Code: "#FF0000" Docs: "#A90217" - Name: 'low_value_color' Code: "#00FF00" Docs: "#2166AC" - ``` - -* checking installed package size ... NOTE - ``` - installed size is 6.0Mb - sub-directories of 1Mb or more: - doc 5.7Mb - ``` - -* checking R code for possible problems ... NOTE - ``` - .Extract2DrugPlotData: no visible binding for global variable - ‘input_type’ - .Extract2DrugPlotData: no visible binding for global variable - ‘block_id’ - .Extract2DrugPlotData: no visible binding for global variable ‘value’ - .Extract2DrugPlotData: no visible binding for global variable ‘left’ - .Extract2DrugPlotData: no visible binding for global variable ‘right’ - .Extract2DrugPlotData: no visible binding for global variable ‘conc1’ - .Extract2DrugPlotData: no visible binding for global variable ‘conc2’ - .Extract2DrugPlotData: no visible binding for global variable ‘text’ - ... - block_id color conc1 conc2 css data end head id input_type label left - maxn metric n nn pred r response response_CI95 response_mean - response_origin response_origin_CI95 response_origin_mean - response_origin_sd response_origin_sem response_sd response_sem right - start synergy text theta value x y - Consider adding - importFrom("graphics", "text") - importFrom("stats", "end", "start") - importFrom("utils", "data", "head") - to your NAMESPACE file. - ``` - -# tableschema.r - -
- -* Version: 1.1.1 -* GitHub: https://github.com/frictionlessdata/tableschema-r -* Source code: https://github.com/cran/tableschema.r -* Date/Publication: 2020-03-12 12:40:02 UTC -* Number of recursive dependencies: 65 - -Run `revdep_details(, "tableschema.r")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘iterators’ - All declared Imports should be used. - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘parsedate’ - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# targeted - -
- -* Version: 0.2.0 -* GitHub: https://github.com/kkholst/targeted -* Source code: https://github.com/cran/targeted -* Date/Publication: 2021-10-26 14:40:02 UTC -* Number of recursive dependencies: 76 - -Run `revdep_details(, "targeted")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 13.6Mb - sub-directories of 1Mb or more: - libs 12.7Mb - ``` - -# text - -
- -* Version: 0.9.50 -* GitHub: https://github.com/OscarKjell/text -* Source code: https://github.com/cran/text -* Date/Publication: 2022-02-12 23:10:02 UTC -* Number of recursive dependencies: 148 - -Run `revdep_details(, "text")` for more info - -
- -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 3 marked UTF-8 strings - ``` - -# TreeSearch - -
- -* Version: 1.1.1 -* GitHub: https://github.com/ms609/TreeSearch -* Source code: https://github.com/cran/TreeSearch -* Date/Publication: 2022-03-22 10:10:28 UTC -* Number of recursive dependencies: 115 - -Run `revdep_details(, "TreeSearch")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.8Mb - sub-directories of 1Mb or more: - datasets 1.6Mb - libs 2.2Mb - ``` - -# TriDimRegression - -
- -* Version: 1.0.1 -* GitHub: https://github.com/alexander-pastukhov/tridim-regression -* Source code: https://github.com/cran/TriDimRegression -* Date/Publication: 2021-10-05 08:30:08 UTC -* Number of recursive dependencies: 98 - -Run `revdep_details(, "TriDimRegression")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 41.3Mb - sub-directories of 1Mb or more: - libs 40.7Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘RcppParallel’ ‘rstantools’ - All declared Imports should be used. - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# tsfeatures - -
- -* Version: 1.0.2 -* GitHub: https://github.com/robjhyndman/tsfeatures -* Source code: https://github.com/cran/tsfeatures -* Date/Publication: 2020-06-07 16:10:02 UTC -* Number of recursive dependencies: 98 - -Run `revdep_details(, "tsfeatures")` for more info - -
- -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# TSstudio - -
- -* Version: 0.1.6 -* GitHub: https://github.com/RamiKrispin/TSstudio -* Source code: https://github.com/cran/TSstudio -* Date/Publication: 2020-01-21 05:30:02 UTC -* Number of recursive dependencies: 142 - -Run `revdep_details(, "TSstudio")` for more info - -
- -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘forecastHybrid’ - All declared Imports should be used. - ``` - -# txshift - -
- -* Version: 0.3.8 -* GitHub: https://github.com/nhejazi/txshift -* Source code: https://github.com/cran/txshift -* Date/Publication: 2022-02-09 22:30:02 UTC -* Number of recursive dependencies: 110 - -Run `revdep_details(, "txshift")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package which this enhances but not available for checking: ‘sl3’ - ``` - -# UCSCXenaShiny - -
- -* Version: 1.1.7 -* GitHub: https://github.com/openbiox/UCSCXenaShiny -* Source code: https://github.com/cran/UCSCXenaShiny -* Date/Publication: 2022-04-13 07:52:38 UTC -* Number of recursive dependencies: 187 - -Run `revdep_details(, "UCSCXenaShiny")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.0Mb - sub-directories of 1Mb or more: - doc 1.1Mb - shinyapp 3.3Mb - ``` - -# updog - -
- -* Version: 2.1.2 -* GitHub: https://github.com/dcgerard/updog -* Source code: https://github.com/cran/updog -* Date/Publication: 2022-01-24 21:50:02 UTC -* Number of recursive dependencies: 145 - -Run `revdep_details(, "updog")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.7Mb - sub-directories of 1Mb or more: - libs 6.0Mb - ``` - -# vmeasur - -
- -* Version: 0.1.4 -* GitHub: NA -* Source code: https://github.com/cran/vmeasur -* Date/Publication: 2021-11-11 19:00:02 UTC -* Number of recursive dependencies: 122 - -Run `revdep_details(, "vmeasur")` for more info - -
- -## In both - -* checking whether package ‘vmeasur’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: no DISPLAY variable so Tk is not available - See ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/00install.out’ for details. - ``` - -# XNAString - -
- -* Version: 1.2.2 -* GitHub: NA -* Source code: https://github.com/cran/XNAString -* Date/Publication: 2021-11-30 -* Number of recursive dependencies: 98 - -Run `revdep_details(, "XNAString")` for more info - -
- -## In both - -* checking installed package size ... NOTE - ``` - installed size is 10.8Mb - sub-directories of 1Mb or more: - libs 9.7Mb - ``` - -* checking top-level files ... NOTE - ``` - File - LICENSE - is not mentioned in the DESCRIPTION file. - ``` - -* checking compiled code ... NOTE - ``` - File ‘XNAString/libs/XNAString.so’: - Found ‘rand’, possibly from ‘rand’ (C) - Object: ‘./ViennaRNA/utils/utils.o’ - Found ‘srand’, possibly from ‘srand’ (C) - Object: ‘./ViennaRNA/utils/utils.o’ - - Compiled code should not call entry points which might terminate R nor - write to stdout/stderr instead of to the console, nor use Fortran I/O - nor system RNGs. - - See ‘Writing portable packages’ in the ‘Writing R Extensions’ manual. - ``` - diff --git a/revdep/problems.md b/revdep/problems.md index 4ae3bc68..154a01d2 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -88,6 +88,31 @@ Run `revdep_details(, "AlpsNMR")` for more info Execution halted ``` +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + --- re-building ‘Vig01-introduction-to-alpsnmr.Rmd’ using rmarkdown + Warning in has_utility("pdfcrop") : + pdfcrop not installed or not in PATH + sh: pdfcrop: command not found + Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : + error in running command + sh: pdfcrop: command not found + Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : + error in running command + ... + Warning: (fancyhdr) \setlength{\headheight}{46.27916pt}. + Warning: (fancyhdr) You might also make \topmargin smaller to compensate: + Warning: (fancyhdr) \addtolength{\topmargin}{-3.60004pt}. + --- finished re-building ‘Vig02-handling-metadata-and-annotations.Rmd’ + + SUMMARY: processing the following file failed: + ‘Vig01b-introduction-to-alpsnmr-old-api.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + # aroma.core
@@ -141,7 +166,7 @@ Run `revdep_details(, "BAMBI")` for more info * GitHub: https://github.com/BillPetti/baseballr * Source code: https://github.com/cran/baseballr * Date/Publication: 2022-09-09 07:52:55 UTC -* Number of recursive dependencies: 117 +* Number of recursive dependencies: 118 Run `revdep_details(, "baseballr")` for more info @@ -152,23 +177,23 @@ Run `revdep_details(, "baseballr")` for more info * checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: - ... --- re-building ‘baseballr.Rmd’ using rmarkdown --- finished re-building ‘baseballr.Rmd’ --- re-building ‘ncaa_scraping.Rmd’ using rmarkdown - --- finished re-building ‘ncaa_scraping.Rmd’ + Quitting from lines 30-34 (ncaa_scraping.Rmd) + Error: processing vignette 'ncaa_scraping.Rmd' failed with diagnostics: + no applicable method for 'select' applied to an object of class "function" + --- failed re-building ‘ncaa_scraping.Rmd’ - --- re-building ‘plotting_statcast.Rmd’ using rmarkdown - --- finished re-building ‘plotting_statcast.Rmd’ ... Quitting from lines 38-40 (using_statcast_pitch_data.Rmd) Error: processing vignette 'using_statcast_pitch_data.Rmd' failed with diagnostics: HTTP error 404. --- failed re-building ‘using_statcast_pitch_data.Rmd’ - SUMMARY: processing the following file failed: - ‘using_statcast_pitch_data.Rmd’ + SUMMARY: processing the following files failed: + ‘ncaa_scraping.Rmd’ ‘using_statcast_pitch_data.Rmd’ Error: Vignette re-building failed. Execution halted @@ -724,11 +749,11 @@ Run `revdep_details(, "EFAtools")` for more info
-* Version: 0.1.15 +* Version: 0.1.17 * GitHub: https://github.com/lance-waller-lab/envi * Source code: https://github.com/cran/envi -* Date/Publication: 2022-08-30 07:00:16 UTC -* Number of recursive dependencies: 156 +* Date/Publication: 2023-02-02 00:40:02 UTC +* Number of recursive dependencies: 153 Run `revdep_details(, "envi")` for more info @@ -1033,6 +1058,42 @@ Run `revdep_details(, "hackeRnews")` for more info ## In both +* checking examples ... ERROR + ``` + Running examples in ‘hackeRnews-Ex.R’ failed + The error most likely occurred in: + + > ### Name: get_best_stories + > ### Title: Hacker News best stories + > ### Aliases: get_best_stories + > + > ### ** Examples + > + > # get the best story on Hacker News + > best_story <- get_best_stories(max_items = 1) + Error in curl::curl_fetch_memory(url, handle = handle) : + Received HTTP code 503 from proxy after CONNECT + Calls: get_best_stories ... request_fetch -> request_fetch.write_memory -> + Execution halted + ``` + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘hackeRnews-specs.Rmd’ using rmarkdown + Quitting from lines 43-45 (hackeRnews-specs.Rmd) + Error: processing vignette 'hackeRnews-specs.Rmd' failed with diagnostics: + Received HTTP code 503 from proxy after CONNECT + --- failed re-building ‘hackeRnews-specs.Rmd’ + + SUMMARY: processing the following file failed: + ‘hackeRnews-specs.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + * checking LazyData ... NOTE ``` 'LazyData' is specified without a 'data' directory @@ -1390,23 +1451,27 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 42821 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 - + Running ‘testthat.R’ ERROR Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > Sys.setenv("R_TESTS" = "") - > - > library(testthat) - > library(lidR) - > test_check("lidR") - Tests using raster: terra - Tests using future: TRUE - Tests using OpenMP thread: 16 - OGR: Unsupported geometry type - OGR: Unsupported geometry type - terminate called after throwing an instance of 'std::length_error' - what(): basic_string::_S_create + Last 50 lines of output: + 3. └─lidR (local) algorithm(st_bbox(las)) + 4. └─lidR:::crop_special_its(treetops, chm, bbox) + 5. └─lidR:::raster_crop(chm, bbox) + 6. ├─sf::st_crop(raster, bbox) + 7. └─stars:::st_crop.stars(raster, bbox) + ── Error ('test-segment_trees.R:147'): Silva algorithm works with sfc ────────── + ... + 7. └─lidR:::segment_trees.LAS(las, silva2016(chm, ttops_shifted500)) + 8. └─lidR (local) algorithm(st_bbox(las)) + 9. └─lidR:::crop_special_its(treetops, chm, bbox) + 10. └─lidR:::raster_crop(chm, bbox) + 11. ├─sf::st_crop(raster, bbox) + 12. └─stars:::st_crop.stars(raster, bbox) + + [ FAIL 20 | WARN 3 | SKIP 40 | PASS 1357 ] + Error: Test failures + Execution halted ``` * checking installed package size ... NOTE @@ -1798,6 +1863,39 @@ Run `revdep_details(, "oncomsm")` for more info GNU make is a SystemRequirements. ``` +# onemapsgapi + +
+ +* Version: 1.1.0 +* GitHub: NA +* Source code: https://github.com/cran/onemapsgapi +* Date/Publication: 2022-11-29 08:00:03 UTC +* Number of recursive dependencies: 70 + +Run `revdep_details(, "onemapsgapi")` for more info + +
+ +## In both + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘onemapsgapi_vignette.Rmd’ using rmarkdown + Quitting from lines 36-37 (onemapsgapi_vignette.Rmd) + Error: processing vignette 'onemapsgapi_vignette.Rmd' failed with diagnostics: + Received HTTP code 503 from proxy after CONNECT + --- failed re-building ‘onemapsgapi_vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘onemapsgapi_vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + # OOS
@@ -1814,6 +1912,23 @@ Run `revdep_details(, "OOS")` for more info ## In both +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘basic_introduction.Rmd’ using rmarkdown + Quitting from lines 31-49 (basic_introduction.Rmd) + Error: processing vignette 'basic_introduction.Rmd' failed with diagnostics: + object 'UNRATE' not found + --- failed re-building ‘basic_introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘basic_introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + * checking LazyData ... NOTE ``` 'LazyData' is specified without a 'data' directory @@ -2182,13 +2297,13 @@ Run `revdep_details(, "reproducible")` for more info * checking tests ... ``` - Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 38301 Segmentation fault ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 7156 Segmentation fault ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 ERROR Running the tests in ‘tests/test-all.R’ failed. Last 50 lines of output: - adding: scratch/henrik/RtmpHcmK4b/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) - adding: scratch/henrik/RtmpHcmK4b/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) + adding: scratch/henrik/RtmpcbGlaK/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) + adding: scratch/henrik/RtmpcbGlaK/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) *** caught segfault *** address 0x40, cause 'memory not mapped' @@ -2397,6 +2512,31 @@ Run `revdep_details(, "sentopics")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > + > library("testthat") + > library("sentopics") + > + > if (Sys.getenv("R_COVR") != "true") { + + test_check("sentopics") + ... + Backtrace: + ▆ + 1. └─sentopics:::get_ECB_press_conferences(years = 1998) at test-others.R:2:2 + 2. └─base::lapply(...) + 3. └─sentopics (local) FUN(X[[i]], ...) + 4. └─utils::download.file(...) + + [ FAIL 1 | WARN 2 | SKIP 1 | PASS 321 ] + Error: Test failures + Execution halted + ``` + * checking installed package size ... NOTE ``` installed size is 8.0Mb @@ -2692,11 +2832,11 @@ Run `revdep_details(, "spaMM")` for more info
-* Version: 0.2.6 +* Version: 0.2.7 * GitHub: https://github.com/machiela-lab/sparrpowR * Source code: https://github.com/cran/sparrpowR -* Date/Publication: 2022-12-02 09:40:09 UTC -* Number of recursive dependencies: 97 +* Date/Publication: 2023-02-02 01:00:02 UTC +* Number of recursive dependencies: 133 Run `revdep_details(, "sparrpowR")` for more info From e8c8a9a7adfcb2be8e5ee4f665b10a58665ff291 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 9 Feb 2023 12:56:25 -0800 Subject: [PATCH 50/88] Be more conservative and de-escalate the local=FALSE error to a warning when {civis} runs in batch mode; in interactive mode, it's defunct [#382] --- DESCRIPTION | 2 +- R/Future-class.R | 7 ++++--- 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 538b339b..672e7e41 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9002 +Version: 1.31.0-9003 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/Future-class.R b/R/Future-class.R index 69483365..210f7086 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -171,14 +171,15 @@ Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdou ## SPECIAL CASE: Temporarily allow the 'civis' package to keep using ## 'local' for a tad longer, although it has zero effect since a ## long time (https://github.com/civisanalytics/civis-r/issues/244) - ## Only allow for this is local = TRUE. - ## /HB 2023-01-27 + ## Only allow for this is local = TRUE and interactive mode (to + ## prevent it from breaking 'R CMD check') + ## /HB 2023-02-09 if (isTRUE(args$local) && Sys.getenv("R_FUTURE_CHECK_IGNORE_CIVIS", "true") == "true") { for (call in sys.calls()) { if ("CivisFuture" %in% as.character(call[[1]])) { msg <- sprintf("%s. In this case it was because civis::CivisFuture() was used. Please contact the maintainers of the 'civis' package about this problem.", msg) - dfcn <- .Deprecated + if (!interactive()) dfcn <- .Deprecated break } } From 415bb49a9f0577c2342e71bdd54a7630d0701104 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 9 Feb 2023 15:15:26 -0800 Subject: [PATCH 51/88] REVDEP: Recheck new and updated packages so now there are 278 revdep packages [ci skip] --- revdep/README.md | 22 ++++++----- revdep/cran.md | 2 +- revdep/problems.md | 98 ++++++++++++++++++++-------------------------- 3 files changed, 55 insertions(+), 67 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 01ac23fd..328387bf 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,14 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-02 | +|date |2023-02-09 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9002 |* | +|future |1.31.0 |1.31.0-9003 |* | |codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -26,7 +26,7 @@ # Revdeps -## All (276) +## All (278) |package |version |error |warning |note | |:------------------------|:---------|:-----|:-------|:----| @@ -42,7 +42,7 @@ |bamm |0.4.3 | | | | |[baseballr](problems.md#baseballr)|1.3.0 |1 | | | |BatchGetSymbols |2.6.4 | | | | -|[batchtools](problems.md#batchtools)|0.9.15 | | |2 | +|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | |bayesian |0.0.9 | | | | |bayesmove |0.2.1 | | | | |bcmaps |1.1.0 | | | | @@ -52,7 +52,7 @@ |[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | |bkmrhat |1.1.3 | | | | |[blavaan](problems.md#blavaan)|0.4-3 | | |3 | -|[blockCV](problems.md#blockcv)|2.1.4 | | |2 | +|[blockCV](problems.md#blockcv)|3.0-0 |1 | |2 | |bolasso |0.2.0 | | | | |[brms](problems.md#brms) |2.18.0 | | |2 | |brpop |0.1.5 | | | | @@ -76,7 +76,7 @@ |delayed |0.4.0 | | | | |dhReg |0.1.1 | | | | |[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | -|[disk.frame](problems.md#diskframe)|0.7.2 |1 | | | +|disk.frame |0.8.0 | | | | |[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | |doFuture |0.12.2 | | | | |DQAstats |0.3.2 | | | | @@ -87,6 +87,7 @@ |dsos |0.1.1 | | | | |DT |0.27 | | | | |easyalluvial |0.3.1 | | | | +|ecic |0.0.2 | | | | |[EFAtools](problems.md#efatools)|0.4.4 | | |2 | |elevatr |0.4.2 | | | | |[envi](problems.md#envi) |0.1.17 | |1 | | @@ -98,7 +99,7 @@ |fastRhockey |0.4.0 | | | | |[fect](problems.md#fect) |1.0.0 | | |2 | |fiery |1.1.4 | | | | -|finbif |0.7.1 | | | | +|finbif |0.7.2 | | | | |[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | |[foieGras](problems.md#foiegras)|0.7-6 | | |1 | |[forecastML](problems.md#forecastml)|0.9.0 | | |1 | @@ -112,7 +113,7 @@ |future.tests |0.5.0 | | | | |fxTWAPLS |0.1.2 | | | | |genBaRcode |1.2.5 | | | | -|[geocmeans](problems.md#geocmeans)|0.3.2 | | |1 | +|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | |GetBCBData |0.7.0 | | | | |[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | |googlePubsubR |0.0.3 | | | | @@ -207,10 +208,10 @@ |PINstimation |0.1.1 | | | | |[PLNmodels](problems.md#plnmodels)|1.0.0 | | |1 | |plumber |1.2.1 | | | | -|polle |1.0 | | | | +|polle |1.2 | | | | |POMADE |0.1.0 | | | | |[portvine](problems.md#portvine)|1.0.2 | | |1 | -|powRICLPM |0.1.0 | | | | +|powRICLPM |0.1.1 | | | | |[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | |[prewas](problems.md#prewas)|1.1.1 | | |1 | |progressr |0.13.0 | | | | @@ -302,6 +303,7 @@ |[updog](problems.md#updog)|2.1.3 | | |1 | |[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | |webdeveloper |1.0.5 | | | | +|whitewater |0.1.2 | | | | |wildmeta |0.3.0 | | | | |[wru](problems.md#wru) |1.0.1 | | |2 | |[XNAString](problems.md#xnastring)|1.6.0 | | |3 | diff --git a/revdep/cran.md b/revdep/cran.md index e292b8a3..a6244ee5 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,6 +1,6 @@ ## revdepcheck results -We checked 276 reverse dependencies (257 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 278 reverse dependencies (259 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. * We saw 0 new problems * We failed to check 0 packages diff --git a/revdep/problems.md b/revdep/problems.md index 154a01d2..ed6a45ba 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -203,10 +203,10 @@ Run `revdep_details(, "baseballr")` for more info
-* Version: 0.9.15 +* Version: 0.9.16 * GitHub: https://github.com/mllg/batchtools * Source code: https://github.com/cran/batchtools -* Date/Publication: 2021-01-11 12:40:03 UTC +* Date/Publication: 2023-02-03 13:52:38 UTC * Number of recursive dependencies: 82 Run `revdep_details(, "batchtools")` for more info @@ -323,7 +323,7 @@ Run `revdep_details(, "bistablehistory")` for more info * GitHub: NA * Source code: https://github.com/cran/blavaan * Date/Publication: 2022-05-11 17:00:05 UTC -* Number of recursive dependencies: 98 +* Number of recursive dependencies: 99 Run `revdep_details(, "blavaan")` for more info @@ -352,11 +352,11 @@ Run `revdep_details(, "blavaan")` for more info
-* Version: 2.1.4 +* Version: 3.0-0 * GitHub: https://github.com/rvalavi/blockCV * Source code: https://github.com/cran/blockCV -* Date/Publication: 2021-06-17 04:50:02 UTC -* Number of recursive dependencies: 123 +* Date/Publication: 2023-02-06 11:42:35 UTC +* Number of recursive dependencies: 131 Run `revdep_details(, "blockCV")` for more info @@ -364,11 +364,38 @@ Run `revdep_details(, "blockCV")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + |================================================================ | 92% + | + |================================================================= | 92% + | + |================================================================= | 93% + | + ... + Error in `sf::st_distance(rx, x[x_1s, ])`: st_crs(x) == st_crs(y) is not TRUE + Backtrace: + ▆ + 1. └─blockCV::cv_nndm(...) at test-cv_nndm.R:71:12 + 2. └─sf::st_distance(rx, x[x_1s, ]) + 3. └─base::stopifnot(st_crs(x) == st_crs(y)) + + [ FAIL 1 | WARN 0 | SKIP 1 | PASS 306 ] + Error: Test failures + Execution halted + ``` + * checking installed package size ... NOTE ``` - installed size is 8.6Mb + installed size is 6.9Mb sub-directories of 1Mb or more: - extdata 7.7Mb + doc 3.6Mb + extdata 1.8Mb + libs 1.2Mb ``` * checking Rd cross-references ... NOTE @@ -530,7 +557,7 @@ Run `revdep_details(, "codebook")` for more info * GitHub: https://github.com/M-E-Rademaker/cSEM * Source code: https://github.com/cran/cSEM * Date/Publication: 2022-11-24 17:50:05 UTC -* Number of recursive dependencies: 126 +* Number of recursive dependencies: 127 Run `revdep_details(, "cSEM")` for more info @@ -612,47 +639,6 @@ Run `revdep_details(, "dipsaus")` for more info libs 3.3Mb ``` -# disk.frame - -
- -* Version: 0.7.2 -* GitHub: https://github.com/DiskFrame/disk.frame -* Source code: https://github.com/cran/disk.frame -* Date/Publication: 2022-03-07 11:40:02 UTC -* Number of recursive dependencies: 103 - -Run `revdep_details(, "disk.frame")` for more info - -
- -## In both - -* checking examples ... ERROR - ``` - Running examples in ‘disk.frame-Ex.R’ failed - The error most likely occurred in: - - > ### Name: anti_join.disk.frame - > ### Title: Performs join/merge for disk.frames - > ### Aliases: anti_join.disk.frame full_join.disk.frame - > ### inner_join.disk.frame left_join.disk.frame semi_join.disk.frame - > - > ### ** Examples - > - ... - Appending disk.frames: - Error in anti_join(.x, .y, by = by, copy = copy, ..., overwrite = overwrite) : - `...` must be empty. - ✖ Problematic arguments: - • ..1 = xch - • ..2 = ych - • overwrite = overwrite - ℹ Did you forget to name an argument? - Calls: anti_join ... resolve.list -> signalConditionsASAP -> signalConditions - Execution halted - ``` - # dispositionEffect
@@ -724,7 +710,7 @@ Run `revdep_details(, "dragon")` for more info * GitHub: https://github.com/mdsteiner/EFAtools * Source code: https://github.com/cran/EFAtools * Date/Publication: 2023-01-06 14:50:40 UTC -* Number of recursive dependencies: 91 +* Number of recursive dependencies: 92 Run `revdep_details(, "EFAtools")` for more info @@ -904,10 +890,10 @@ Run `revdep_details(, "forecastML")` for more info
-* Version: 0.3.2 +* Version: 0.3.3 * GitHub: https://github.com/JeremyGelb/geocmeans * Source code: https://github.com/cran/geocmeans -* Date/Publication: 2023-01-08 21:40:02 UTC +* Date/Publication: 2023-02-07 01:02:31 UTC * Number of recursive dependencies: 197 Run `revdep_details(, "geocmeans")` for more info @@ -918,11 +904,11 @@ Run `revdep_details(, "geocmeans")` for more info * checking installed package size ... NOTE ``` - installed size is 14.3Mb + installed size is 14.6Mb sub-directories of 1Mb or more: doc 1.7Mb extdata 3.0Mb - libs 8.0Mb + libs 8.2Mb ``` # googleComputeEngineR @@ -1208,7 +1194,7 @@ Run `revdep_details(, "inlinedocs")` for more info * GitHub: NA * Source code: https://github.com/cran/InPAS * Date/Publication: 2022-11-01 -* Number of recursive dependencies: 166 +* Number of recursive dependencies: 167 Run `revdep_details(, "InPAS")` for more info From e7f922273e5905368e397dce80f9b14ec2f326af Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 12 Feb 2023 22:18:46 -0800 Subject: [PATCH 52/88] plan(multiprocess) again produce deprecation warning --- DESCRIPTION | 2 +- R/multiprocess.R | 1 + R/zzz.plan.R | 2 ++ 3 files changed, 4 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 672e7e41..61c017ef 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9003 +Version: 1.31.0-9004 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/multiprocess.R b/R/multiprocess.R index d4e4abdc..16e81606 100644 --- a/R/multiprocess.R +++ b/R/multiprocess.R @@ -42,4 +42,5 @@ multiprocess <- function(..., workers = availableCores(), envir = parent.frame() } class(multiprocess) <- c("sequential", "uniprocess", "future", "function") ## future (> 1.30.0): 'multiprocess' always resolves to 'sequential' +class(multiprocess) <- c(class(multiprocess), "multiprocess") attr(multiprocess, "init") <- FALSE diff --git a/R/zzz.plan.R b/R/zzz.plan.R index 9e5df93a..b573d472 100644 --- a/R/zzz.plan.R +++ b/R/zzz.plan.R @@ -162,6 +162,8 @@ plan <- local({ if (class[1] == strategy) return(TRUE) if (length(class) == 1L) return(FALSE) if (class[1] == "tweaked" && class[2] == strategy) return(TRUE) + ## Special case for strategy == "multiprocess" + if (strategy == "multiprocess" && class[length(class)] == strategy) return(TRUE) FALSE } From 69dbc151d174074e555c418bb866bcf0d1235de0 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 12 Feb 2023 23:34:00 -0800 Subject: [PATCH 53/88] REVDEP: 279 revdep packages where new igraph 1.4.0 fail to install [ci skip] --- revdep/README.md | 116 +-- revdep/cran.md | 13 +- revdep/failures.md | 673 +++++++++++++++- revdep/problems.md | 1852 ++++++++++++++++++++++++++++++-------------- 4 files changed, 2018 insertions(+), 636 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 328387bf..1b1a94c0 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,14 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-09 | +|date |2023-02-12 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9003 |* | +|future |1.31.0 |1.31.0-9004 |* | |codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -26,24 +26,39 @@ # Revdeps -## All (278) +## Failed to check (10) + +|package |version |error |warning |note | +|:------------|:-------|:-----|:-------|:----| +|[AlpsNMR](failures.md#alpsnmr)|4.0.3 |1 | | | +|[bayesian](failures.md#bayesian)|0.0.9 |1 | | | +|[brms](failures.md#brms)|2.18.0 |1 | |1 | +|[ChromSCape](failures.md#chromscape)|1.8.0 |1 | |2 | +|[Prostar](failures.md#prostar)|1.30.5 |1 | | | +|[scBubbletree](failures.md#scbubbletree)|1.0.0 |1 | | | +|[signeR](failures.md#signer)|2.0.2 |1 | | | +|[tarchetypes](failures.md#tarchetypes)|0.7.4 |1 | | | +|[TreeSearch](failures.md#treesearch)|1.2.0 |1 | | | +|[vmeasur](failures.md#vmeasur)|0.1.4 |1 | | | + +## All (279) |package |version |error |warning |note | |:------------------------|:---------|:-----|:-------|:----| |[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | |alookr |0.3.7 | | | | |alphaci |1.0.0 | | | | -|[AlpsNMR](problems.md#alpsnmr)|4.0.2 |3 | | | +|[AlpsNMR](failures.md#alpsnmr)|4.0.3 |1 | | | |arkdb |0.0.16 | | | | |aroma.affymetrix |3.2.1 | | | | |aroma.cn |1.7.0 | | | | |[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | |[BAMBI](problems.md#bambi)|2.3.4 | | |1 | -|bamm |0.4.3 | | | | +|[bamm](problems.md#bamm) |0.4.3 |1 | | | |[baseballr](problems.md#baseballr)|1.3.0 |1 | | | |BatchGetSymbols |2.6.4 | | | | |[batchtools](problems.md#batchtools)|0.9.16 | | |2 | -|bayesian |0.0.9 | | | | +|[bayesian](failures.md#bayesian)|0.0.9 |1 | | | |bayesmove |0.2.1 | | | | |bcmaps |1.1.0 | | | | |[BEKKs](problems.md#bekks)|1.4.1 | | |2 | @@ -51,15 +66,14 @@ |[bigDM](problems.md#bigdm)|0.5.0 | | |2 | |[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | |bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan)|0.4-3 | | |3 | -|[blockCV](problems.md#blockcv)|3.0-0 |1 | |2 | +|[blavaan](problems.md#blavaan)|0.4-6 | | |3 | |bolasso |0.2.0 | | | | -|[brms](problems.md#brms) |2.18.0 | | |2 | +|[brms](failures.md#brms) |2.18.0 |1 | |1 | |brpop |0.1.5 | | | | -|canaper |1.0.0 | | | | -|ceRNAnetsim |1.10.0 | | | | +|[canaper](problems.md#canaper)|1.0.0 |1 | | | +|[ceRNAnetsim](problems.md#cernanetsim)|1.10.0 |1 | | | |cft |1.0.0 | | | | -|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | +|[ChromSCape](failures.md#chromscape)|1.8.0 |1 | |2 | |[civis](problems.md#civis)|3.0.0 | | |1 | |Clustering |1.7.7 | | | | |codalm |0.1.2 | | | | @@ -73,15 +87,15 @@ |cvCovEst |1.2.0 | | | | |dagHMM |0.1.0 | | | | |[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | -|delayed |0.4.0 | | | | +|[delayed](problems.md#delayed)|0.4.0 |1 | | | |dhReg |0.1.1 | | | | |[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | |disk.frame |0.8.0 | | | | |[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | |doFuture |0.12.2 | | | | |DQAstats |0.3.2 | | | | -|[dragon](problems.md#dragon)|1.2.1 | | |1 | -|drake |7.13.4 | | | | +|[dragon](problems.md#dragon)|1.2.1 |1 | | | +|[drake](problems.md#drake)|7.13.4 |1 | | | |drimmR |1.0.1 | | | | |drtmle |1.1.2 | | | | |dsos |0.1.1 | | | | @@ -91,6 +105,7 @@ |[EFAtools](problems.md#efatools)|0.4.4 | | |2 | |elevatr |0.4.2 | | | | |[envi](problems.md#envi) |0.1.17 | |1 | | +|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | |[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | |epwshiftr |0.1.3 | | | | |ezcox |1.0.2 | | | | @@ -100,7 +115,8 @@ |[fect](problems.md#fect) |1.0.0 | | |2 | |fiery |1.1.4 | | | | |finbif |0.7.2 | | | | -|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | +|fitlandr |0.1.0 | | | | +|[flowGraph](problems.md#flowgraph)|1.6.0 |1 | | | |[foieGras](problems.md#foiegras)|0.7-6 | | |1 | |[forecastML](problems.md#forecastml)|0.9.0 | | |1 | |fst4pg |1.0.0 | | | | @@ -112,13 +128,13 @@ |future.callr |0.8.1 | | | | |future.tests |0.5.0 | | | | |fxTWAPLS |0.1.2 | | | | -|genBaRcode |1.2.5 | | | | +|[genBaRcode](problems.md#genbarcode)|1.2.5 |1 | | | |[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | |GetBCBData |0.7.0 | | | | |[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | |googlePubsubR |0.0.3 | | | | |[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | -|[greed](problems.md#greed)|0.6.1 | | |2 | +|[greed](problems.md#greed)|0.6.1 | | |3 | |greta |0.4.3 | | | | |gstat |2.1-0 | | | | |GSVA |1.46.0 | | | | @@ -126,7 +142,7 @@ |gtfs2emis |0.1.0 | | | | |gtfs2gps |2.1-0 | | | | |[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews)|0.1.0 |2 | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | |hacksig |0.1.2 | | | | |[hal9001](problems.md#hal9001)|0.4.3 | | |1 | |haldensify |0.2.3 | | | | @@ -136,7 +152,7 @@ |imagefluency |0.2.4 | | | | |iml |0.11.1 | | | | |incubate |1.2.0 | | | | -|[infercnv](problems.md#infercnv)|1.14.0 | | |2 | +|[infercnv](problems.md#infercnv)|1.14.0 |1 | | | |[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | |[InPAS](problems.md#inpas)|2.6.0 | | |1 | |[interflex](problems.md#interflex)|1.2.6 | | |1 | @@ -150,7 +166,7 @@ |kernelboot |0.1.9 | | | | |[keyATM](problems.md#keyatm)|0.4.2 | | |1 | |latentcor |2.0.1 | | | | -|lava |1.7.1 | | | | +|[lava](problems.md#lava) |1.7.1 | | |1 | |ldaPrototype |0.3.1 | | | | |ldsr |0.0.2 | | | | |lemna |1.0.0 | | | | @@ -170,14 +186,14 @@ |[mice](problems.md#mice) |3.15.0 | |1 | | |[microservices](problems.md#microservices)|0.2.0 |1 | | | |microSTASIS |0.1.0 | | | | -|migraph |0.13.2 | | | | +|[migraph](problems.md#migraph)|0.13.2 |1 | | | |mikropml |1.5.0 | | | | -|[MineICA](problems.md#mineica)|1.38.0 | |3 |4 | -|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | -|mistyR |1.6.0 | | | | +|[MineICA](problems.md#mineica)|1.38.0 |1 | | | +|[missSBM](problems.md#misssbm)|1.0.3 |1 | | | +|[mistyR](problems.md#mistyr)|1.6.0 |3 | |1 | |mlr3 |0.14.1 | | | | |mlr3db |0.5.0 | | | | -|mlr3pipelines |0.4.2 | | | | +|[mlr3pipelines](problems.md#mlr3pipelines)|0.4.2 |2 | |1 | |mlr3spatial |0.3.1 | | | | |modelsummary |1.3.0 | | | | |[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | @@ -185,15 +201,15 @@ |mrgsim.parallel |0.2.1 | | | | |[mslp](problems.md#mslp) |1.0.1 |1 | | | |multiverse |0.6.1 | | | | -|netShiny |1.0 | | | | +|[netShiny](problems.md#netshiny)|1.0 |1 | | | |NetSimR |0.1.2 | | | | |nfl4th |1.0.2 | | | | |nflfastR |4.5.1 | | | | |nflseedR |1.2.0 | | | | -|nncc |1.0.0 | | | | +|[nncc](problems.md#nncc) |1.0.0 |1 | | | |[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | -|[onemapsgapi](problems.md#onemapsgapi)|1.1.0 |1 | | | -|[OOS](problems.md#oos) |1.0.0 |1 | |1 | +|onemapsgapi |1.1.0 | | | | +|[OOS](problems.md#oos) |1.0.0 | | |1 | |origami |1.0.7 | | | | |paramsim |0.1.0 | | | | |[partR2](problems.md#partr2)|0.9.1 | | |1 | @@ -202,23 +218,23 @@ |PCRedux |1.1-2 | | | | |PeakSegDisk |2022.2.1 | | | | |penaltyLearning |2020.5.13 | | | | -|pGRN |0.3.5 | | | | +|[pGRN](problems.md#pgrn) |0.3.5 |1 | | | |[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | |[phylolm](problems.md#phylolm)|2.6.2 | | |1 | |PINstimation |0.1.1 | | | | -|[PLNmodels](problems.md#plnmodels)|1.0.0 | | |1 | +|[PLNmodels](problems.md#plnmodels)|1.0.1 |1 | | | |plumber |1.2.1 | | | | |polle |1.2 | | | | |POMADE |0.1.0 | | | | |[portvine](problems.md#portvine)|1.0.2 | | |1 | |powRICLPM |0.1.1 | | | | |[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | -|[prewas](problems.md#prewas)|1.1.1 | | |1 | +|[prewas](problems.md#prewas)|1.1.1 |2 | |1 | |progressr |0.13.0 | | | | -|[projpred](problems.md#projpred)|2.3.0 | | |1 | +|[projpred](problems.md#projpred)|2.4.0 |1 | |1 | |[promises](problems.md#promises)|1.2.0.1 | | |1 | -|Prostar |1.30.3 | | | | -|protti |0.6.0 | | | | +|[Prostar](failures.md#prostar)|1.30.5 |1 | | | +|[protti](problems.md#protti)|0.6.0 | | |1 | |PSCBS |0.66.0 | | | | |PUMP |1.0.1 | | | | |qape |2.0 | | | | @@ -226,35 +242,35 @@ |qgcomp |2.10.1 | | | | |qgcompint |0.7.0 | | | | |[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | -|rangeMapper |2.0.3 | | | | +|[rangeMapper](problems.md#rangemapper)|2.0.3 | | |1 | |rBiasCorrection |0.3.4 | | | | |receptiviti |0.1.3 | | | | |refineR |1.5.1 | | | | |[regmedint](problems.md#regmedint)|1.0.0 | | |1 | |remiod |1.0.2 | | | | -|[reproducible](problems.md#reproducible)|1.2.16 |1 | | | +|reproducible |1.2.16 |-1 | | | |reval |3.1-0 | | | | |[rgee](problems.md#rgee) |1.1.5 | | |2 | |[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | |robust2sls |0.2.2 | | | | |RTransferEntropy |0.2.21 | | | | |[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | -|scBubbletree |1.0.0 | | | | -|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | +|[scBubbletree](failures.md#scbubbletree)|1.0.0 |1 | | | +|[scDiffCom](problems.md#scdiffcom)|0.1.0 |1 | |2 | |SCtools |0.3.2.1 | | | | |[sctransform](problems.md#sctransform)|0.3.5 | | |1 | |[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | |[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | |seer |1.1.8 | | | | |semtree |0.9.18 | | | | -|[sentopics](problems.md#sentopics)|0.7.1 |1 | |3 | -|[Seurat](problems.md#seurat)|4.3.0 | | |2 | +|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[Seurat](problems.md#seurat)|4.3.0 |1 | | | |[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | |[shiny](problems.md#shiny)|1.7.4 | | |1 | |[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | |sigminer |2.1.9 | | | | |Signac |1.9.0 | | | | -|[signeR](problems.md#signer)|2.0.2 | | |3 | +|[signeR](failures.md#signer)|2.0.2 |1 | | | |[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | |simfinapi |0.2.0 | | | | |simglm |0.8.9 | | | | @@ -264,18 +280,18 @@ |[skpr](problems.md#skpr) |1.1.6 | | |1 | |smoots |1.1.3 | | | | |sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude)|1.1.3 | | |1 | +|[solitude](problems.md#solitude)|1.1.3 |1 | | | |sovereign |1.2.1 | | | | |[spaMM](problems.md#spamm)|4.1.20 | | |2 | |[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | |[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | |[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | |[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | -|specr |1.0.0 | | | | +|[specr](problems.md#specr)|1.0.0 |1 | | | |sperrorest |3.0.5 | | | | |spFSR |2.0.3 | | | | |[sphunif](problems.md#sphunif)|1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | +|[spNetwork](problems.md#spnetwork)|0.4.3.6 |1 | | | |[squat](problems.md#squat)|0.1.0 | | |1 | |[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | |[stars](problems.md#stars)|0.6-0 | | |2 | @@ -284,9 +300,9 @@ |supercells |0.9.1 | | | | |[synergyfinder](problems.md#synergyfinder)|3.6.2 | |1 |2 | |[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | -|tarchetypes |0.7.4 | | | | +|[tarchetypes](failures.md#tarchetypes)|0.7.4 |1 | | | |[targeted](problems.md#targeted)|0.3 | | |1 | -|targets |0.14.2 | | | | +|[targets](problems.md#targets)|0.14.2 |1 | | | |tcplfit2 |0.1.3 | | | | |tealeaves |1.0.6 | | | | |templr |0.2-0 | | | | @@ -294,14 +310,14 @@ |tglkmeans |0.3.5 | | | | |tidyqwi |0.1.2 | | | | |TKCat |1.0.6 | | | | -|[TreeSearch](problems.md#treesearch)|1.2.0 |1 | |1 | +|[TreeSearch](failures.md#treesearch)|1.2.0 |1 | | | |[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | |tsfeatures |1.1 | | | | |[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | |[txshift](problems.md#txshift)|0.3.8 | | |1 | |[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.9 | | |1 | |[updog](problems.md#updog)|2.1.3 | | |1 | -|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | +|[vmeasur](failures.md#vmeasur)|0.1.4 |1 | | | |webdeveloper |1.0.5 | | | | |whitewater |0.1.2 | | | | |wildmeta |0.3.0 | | | | diff --git a/revdep/cran.md b/revdep/cran.md index a6244ee5..ea832cef 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,7 +1,16 @@ ## revdepcheck results -We checked 278 reverse dependencies (259 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 279 reverse dependencies (260 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. * We saw 0 new problems - * We failed to check 0 packages + * We failed to check 5 packages +Issues with CRAN packages are summarised below. + +### Failed to check + +* bayesian (NA) +* brms (NA) +* tarchetypes (NA) +* TreeSearch (NA) +* vmeasur (NA) diff --git a/revdep/failures.md b/revdep/failures.md index 9a207363..aea9391e 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1 +1,672 @@ -*Wow, no problems at all. :)* \ No newline at end of file +# AlpsNMR + +
+ +* Version: 4.0.3 +* GitHub: https://github.com/sipss/AlpsNMR +* Source code: https://github.com/cran/AlpsNMR +* Date/Publication: 2023-02-10 +* Number of recursive dependencies: 169 + +Run `revdep_details(, "AlpsNMR")` for more info + +
+ +## In both + +* checking whether package ‘AlpsNMR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘AlpsNMR’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘AlpsNMR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/AlpsNMR’ + + +``` +### CRAN + +``` +* installing *source* package ‘AlpsNMR’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘AlpsNMR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/old/AlpsNMR.Rcheck/AlpsNMR’ + + +``` +# bayesian + +
+ +* Version: 0.0.9 +* GitHub: https://github.com/hsbadr/bayesian +* Source code: https://github.com/cran/bayesian +* Date/Publication: 2022-06-16 23:00:02 UTC +* Number of recursive dependencies: 186 + +Run `revdep_details(, "bayesian")` for more info + +
+ +## In both + +* checking whether package ‘bayesian’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘bayesian’ ... +** package ‘bayesian’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘igraph’ +Execution halted +ERROR: lazy loading failed for package ‘bayesian’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/bayesian’ + + +``` +### CRAN + +``` +* installing *source* package ‘bayesian’ ... +** package ‘bayesian’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘igraph’ +Execution halted +ERROR: lazy loading failed for package ‘bayesian’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/old/bayesian.Rcheck/bayesian’ + + +``` +# brms + +
+ +* Version: 2.18.0 +* GitHub: https://github.com/paul-buerkner/brms +* Source code: https://github.com/cran/brms +* Date/Publication: 2022-09-19 13:56:19 UTC +* Number of recursive dependencies: 181 + +Run `revdep_details(, "brms")` for more info + +
+ +## In both + +* checking whether package ‘brms’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘cmdstanr’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘brms’ ... +** package ‘brms’ successfully unpacked and MD5 sums checked +** using staged installation +** R +Warning: namespace ‘brms’ is not available and has been replaced +by .GlobalEnv when processing object ‘brmsfit_example1’ +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘brms’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/brms’ + + +``` +### CRAN + +``` +* installing *source* package ‘brms’ ... +** package ‘brms’ successfully unpacked and MD5 sums checked +** using staged installation +** R +Warning: namespace ‘brms’ is not available and has been replaced +by .GlobalEnv when processing object ‘brmsfit_example1’ +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘brms’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/old/brms.Rcheck/brms’ + + +``` +# ChromSCape + +
+ +* Version: 1.8.0 +* GitHub: https://github.com/vallotlab/ChromSCape +* Source code: https://github.com/cran/ChromSCape +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 227 + +Run `revdep_details(, "ChromSCape")` for more info + +
+ +## In both + +* checking whether package ‘ChromSCape’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘igraph’ + ``` + +* checking for hidden files and directories ... NOTE + ``` + Found the following hidden files and directories: + .BBSoptions + These were most likely included in error. See section ‘Package + structure’ in the ‘Writing R Extensions’ manual. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ChromSCape’ ... +** using staged installation +** libs +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o +g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘ChromSCape’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/ChromSCape’ + + +``` +### CRAN + +``` +* installing *source* package ‘ChromSCape’ ... +** using staged installation +** libs +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o +g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘ChromSCape’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/ChromSCape’ + + +``` +# Prostar + +
+ +* Version: 1.30.5 +* GitHub: https://github.com/prostarproteomics/Prostar +* Source code: https://github.com/cran/Prostar +* Date/Publication: 2023-02-10 +* Number of recursive dependencies: 166 + +Run `revdep_details(, "Prostar")` for more info + +
+ +## In both + +* checking whether package ‘Prostar’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Prostar’ ... +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Prostar’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/Prostar’ + + +``` +### CRAN + +``` +* installing *source* package ‘Prostar’ ... +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Prostar’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/old/Prostar.Rcheck/Prostar’ + + +``` +# scBubbletree + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/snaketron/scBubbletree +* Source code: https://github.com/cran/scBubbletree +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 178 + +Run `revdep_details(, "scBubbletree")` for more info + +
+ +## In both + +* checking whether package ‘scBubbletree’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘scBubbletree’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘scBubbletree’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/scBubbletree’ + + +``` +### CRAN + +``` +* installing *source* package ‘scBubbletree’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘scBubbletree’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/old/scBubbletree.Rcheck/scBubbletree’ + + +``` +# signeR + +
+ +* Version: 2.0.2 +* GitHub: https://github.com/rvalieris/signeR +* Source code: https://github.com/cran/signeR +* Date/Publication: 2023-01-19 +* Number of recursive dependencies: 242 + +Run `revdep_details(, "signeR")` for more info + +
+ +## In both + +* checking whether package ‘signeR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘signeR’ ... +** using staged installation +** libs +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o +g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs +** R +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘signeR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/signeR’ + + +``` +### CRAN + +``` +* installing *source* package ‘signeR’ ... +** using staged installation +** libs +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o +g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs +** R +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘signeR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/signeR’ + + +``` +# tarchetypes + +
+ +* Version: 0.7.4 +* GitHub: https://github.com/ropensci/tarchetypes +* Source code: https://github.com/cran/tarchetypes +* Date/Publication: 2023-01-06 18:50:20 UTC +* Number of recursive dependencies: 78 + +Run `revdep_details(, "tarchetypes")` for more info + +
+ +## In both + +* checking whether package ‘tarchetypes’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘tarchetypes’ ... +** package ‘tarchetypes’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘tarchetypes’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/tarchetypes’ + + +``` +### CRAN + +``` +* installing *source* package ‘tarchetypes’ ... +** package ‘tarchetypes’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘tarchetypes’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/old/tarchetypes.Rcheck/tarchetypes’ + + +``` +# TreeSearch + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/ms609/TreeSearch +* Source code: https://github.com/cran/TreeSearch +* Date/Publication: 2022-08-10 22:40:17 UTC +* Number of recursive dependencies: 117 + +Run `revdep_details(, "TreeSearch")` for more info + +
+ +## In both + +* checking whether package ‘TreeSearch’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘TreeSearch’ ... +** package ‘TreeSearch’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘TreeSearch’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/TreeSearch’ + + +``` +### CRAN + +``` +* installing *source* package ‘TreeSearch’ ... +** package ‘TreeSearch’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘TreeSearch’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/old/TreeSearch.Rcheck/TreeSearch’ + + +``` +# vmeasur + +
+ +* Version: 0.1.4 +* GitHub: NA +* Source code: https://github.com/cran/vmeasur +* Date/Publication: 2021-11-11 19:00:02 UTC +* Number of recursive dependencies: 117 + +Run `revdep_details(, "vmeasur")` for more info + +
+ +## In both + +* checking whether package ‘vmeasur’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘vmeasur’ ... +** package ‘vmeasur’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘vmeasur’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/vmeasur’ + + +``` +### CRAN + +``` +* installing *source* package ‘vmeasur’ ... +** package ‘vmeasur’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘vmeasur’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/old/vmeasur.Rcheck/vmeasur’ + + +``` diff --git a/revdep/problems.md b/revdep/problems.md index ed6a45ba..9a607eb7 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -26,10 +26,10 @@ Run `revdep_details(, "AIPW")` for more info
-* Version: 4.0.2 +* Version: 4.0.3 * GitHub: https://github.com/sipss/AlpsNMR * Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2022-11-10 +* Date/Publication: 2023-02-10 * Number of recursive dependencies: 169 Run `revdep_details(, "AlpsNMR")` for more info @@ -38,81 +38,50 @@ Run `revdep_details(, "AlpsNMR")` for more info ## In both -* checking examples ... ERROR +* checking whether package ‘AlpsNMR’ can be installed ... ERROR ``` - Running examples in ‘AlpsNMR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: models_stability_plot_plsda - > ### Title: Models stability plot - > ### Aliases: models_stability_plot_plsda - > - > ### ** Examples - > - > # Data analysis for a table of integrated peaks - ... - 18. └─vctrs::vec_default_cast(...) - 19. ├─base::withRestarts(...) - 20. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 21. │ └─base (local) doWithOneRestart(return(expr), restart) - 22. └─vctrs::stop_incompatible_cast(...) - 23. └─vctrs::stop_incompatible_type(...) - 24. └─vctrs:::stop_incompatible(...) - 25. └─vctrs:::stop_vctrs(...) - 26. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - Execution halted + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/00install.out’ for details. ``` -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(AlpsNMR) - Loading required package: future - - Attaching package: 'AlpsNMR' - - ... - still_improving = dplyr::cumall(.data$auc_diff_above_thres), - good_ncomp = (.data$still_improving == TRUE & dplyr::lead(.data$still_improving, - default = FALSE) == FALSE))`: ℹ In argument: `good_ncomp = (...)`. - ℹ In group 2: `cv_outer_iteration = 1`, `cv_inner_iteration = 2`. - Caused by error in `vec_c()`: - ! Can't convert `..2` to . - - [ FAIL 1 | WARN 2 | SKIP 1 | PASS 90 ] - Error: Test failures - Execution halted - ``` +## Installation + +### Devel + +``` +* installing *source* package ‘AlpsNMR’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘AlpsNMR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/AlpsNMR’ -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘Vig01-introduction-to-alpsnmr.Rmd’ using rmarkdown - Warning in has_utility("pdfcrop") : - pdfcrop not installed or not in PATH - sh: pdfcrop: command not found - Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : - error in running command - sh: pdfcrop: command not found - Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : - error in running command - ... - Warning: (fancyhdr) \setlength{\headheight}{46.27916pt}. - Warning: (fancyhdr) You might also make \topmargin smaller to compensate: - Warning: (fancyhdr) \addtolength{\topmargin}{-3.60004pt}. - --- finished re-building ‘Vig02-handling-metadata-and-annotations.Rmd’ - - SUMMARY: processing the following file failed: - ‘Vig01b-introduction-to-alpsnmr-old-api.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` +``` +### CRAN + +``` +* installing *source* package ‘AlpsNMR’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘AlpsNMR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/old/AlpsNMR.Rcheck/AlpsNMR’ + + +``` # aroma.core
@@ -158,6 +127,30 @@ Run `revdep_details(, "BAMBI")` for more info libs 6.7Mb ``` +# bamm + +
+ +* Version: 0.4.3 +* GitHub: https://github.com/luismurao/bamm +* Source code: https://github.com/cran/bamm +* Date/Publication: 2022-12-20 11:10:05 UTC +* Number of recursive dependencies: 109 + +Run `revdep_details(, "bamm")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + # baseballr
@@ -177,23 +170,23 @@ Run `revdep_details(, "baseballr")` for more info * checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: + ... --- re-building ‘baseballr.Rmd’ using rmarkdown --- finished re-building ‘baseballr.Rmd’ --- re-building ‘ncaa_scraping.Rmd’ using rmarkdown - Quitting from lines 30-34 (ncaa_scraping.Rmd) - Error: processing vignette 'ncaa_scraping.Rmd' failed with diagnostics: - no applicable method for 'select' applied to an object of class "function" - --- failed re-building ‘ncaa_scraping.Rmd’ + --- finished re-building ‘ncaa_scraping.Rmd’ + --- re-building ‘plotting_statcast.Rmd’ using rmarkdown + --- finished re-building ‘plotting_statcast.Rmd’ ... Quitting from lines 38-40 (using_statcast_pitch_data.Rmd) Error: processing vignette 'using_statcast_pitch_data.Rmd' failed with diagnostics: HTTP error 404. --- failed re-building ‘using_statcast_pitch_data.Rmd’ - SUMMARY: processing the following files failed: - ‘ncaa_scraping.Rmd’ ‘using_statcast_pitch_data.Rmd’ + SUMMARY: processing the following file failed: + ‘using_statcast_pitch_data.Rmd’ Error: Vignette re-building failed. Execution halted @@ -225,6 +218,64 @@ Run `revdep_details(, "batchtools")` for more info Package unavailable to check Rd xrefs: ‘Rmpi’ ``` +# bayesian + +
+ +* Version: 0.0.9 +* GitHub: https://github.com/hsbadr/bayesian +* Source code: https://github.com/cran/bayesian +* Date/Publication: 2022-06-16 23:00:02 UTC +* Number of recursive dependencies: 186 + +Run `revdep_details(, "bayesian")` for more info + +
+ +## In both + +* checking whether package ‘bayesian’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘bayesian’ ... +** package ‘bayesian’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘igraph’ +Execution halted +ERROR: lazy loading failed for package ‘bayesian’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/bayesian’ + + +``` +### CRAN + +``` +* installing *source* package ‘bayesian’ ... +** package ‘bayesian’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘igraph’ +Execution halted +ERROR: lazy loading failed for package ‘bayesian’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/old/bayesian.Rcheck/bayesian’ + + +``` # BEKKs
@@ -319,10 +370,10 @@ Run `revdep_details(, "bistablehistory")` for more info
-* Version: 0.4-3 +* Version: 0.4-6 * GitHub: NA * Source code: https://github.com/cran/blavaan -* Date/Publication: 2022-05-11 17:00:05 UTC +* Date/Publication: 2023-02-11 08:50:09 UTC * Number of recursive dependencies: 99 Run `revdep_details(, "blavaan")` for more info @@ -338,9 +389,10 @@ Run `revdep_details(, "blavaan")` for more info * checking installed package size ... NOTE ``` - installed size is 87.4Mb + installed size is 89.8Mb sub-directories of 1Mb or more: - libs 85.5Mb + libs 87.3Mb + testdata 1.4Mb ``` * checking for GNU extensions in Makefiles ... NOTE @@ -348,17 +400,90 @@ Run `revdep_details(, "blavaan")` for more info GNU make is a SystemRequirements. ``` -# blockCV +# brms
-* Version: 3.0-0 -* GitHub: https://github.com/rvalavi/blockCV -* Source code: https://github.com/cran/blockCV -* Date/Publication: 2023-02-06 11:42:35 UTC -* Number of recursive dependencies: 131 +* Version: 2.18.0 +* GitHub: https://github.com/paul-buerkner/brms +* Source code: https://github.com/cran/brms +* Date/Publication: 2022-09-19 13:56:19 UTC +* Number of recursive dependencies: 181 -Run `revdep_details(, "blockCV")` for more info +Run `revdep_details(, "brms")` for more info + +
+ +## In both + +* checking whether package ‘brms’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘cmdstanr’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘brms’ ... +** package ‘brms’ successfully unpacked and MD5 sums checked +** using staged installation +** R +Warning: namespace ‘brms’ is not available and has been replaced +by .GlobalEnv when processing object ‘brmsfit_example1’ +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘brms’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/brms’ + + +``` +### CRAN + +``` +* installing *source* package ‘brms’ ... +** package ‘brms’ successfully unpacked and MD5 sums checked +** using staged installation +** R +Warning: namespace ‘brms’ is not available and has been replaced +by .GlobalEnv when processing object ‘brmsfit_example1’ +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘brms’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/old/brms.Rcheck/brms’ + + +``` +# canaper + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/ropensci/canaper +* Source code: https://github.com/cran/canaper +* Date/Publication: 2022-10-04 10:20:12 UTC +* Number of recursive dependencies: 167 + +Run `revdep_details(, "canaper")` for more info
@@ -370,66 +495,47 @@ Run `revdep_details(, "blockCV")` for more info ERROR Running the tests in ‘tests/testthat.R’ failed. Last 50 lines of output: - |================================================================ | 92% - | - |================================================================= | 92% - | - |================================================================= | 93% - | + 4. └─base::loadNamespace(x) + 5. ├─base::namespaceImportFrom(...) + 6. │ └─base::asNamespace(ns) + 7. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 8. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) + 9. └─base (local) withOneRestart(expr, restarts[[1L]]) ... - Error in `sf::st_distance(rx, x[x_1s, ])`: st_crs(x) == st_crs(y) is not TRUE - Backtrace: - ▆ - 1. └─blockCV::cv_nndm(...) at test-cv_nndm.R:71:12 - 2. └─sf::st_distance(rx, x[x_1s, ]) - 3. └─base::stopifnot(st_crs(x) == st_crs(y)) + 5. ├─base::namespaceImportFrom(...) + 6. │ └─base::asNamespace(ns) + 7. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 8. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) + 9. └─base (local) withOneRestart(expr, restarts[[1L]]) + 10. └─base (local) doWithOneRestart(return(expr), restart) - [ FAIL 1 | WARN 0 | SKIP 1 | PASS 306 ] + [ FAIL 9 | WARN 0 | SKIP 0 | PASS 99 ] Error: Test failures Execution halted ``` -* checking installed package size ... NOTE - ``` - installed size is 6.9Mb - sub-directories of 1Mb or more: - doc 3.6Mb - extdata 1.8Mb - libs 1.2Mb - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘biomod2’ - ``` - -# brms +# ceRNAnetsim
-* Version: 2.18.0 -* GitHub: https://github.com/paul-buerkner/brms -* Source code: https://github.com/cran/brms -* Date/Publication: 2022-09-19 13:56:19 UTC -* Number of recursive dependencies: 175 +* Version: 1.10.0 +* GitHub: https://github.com/selcenari/ceRNAnetsim +* Source code: https://github.com/cran/ceRNAnetsim +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 99 -Run `revdep_details(, "brms")` for more info +Run `revdep_details(, "ceRNAnetsim")` for more info
## In both -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘cmdstanr’ - ``` - -* checking installed package size ... NOTE +* checking package dependencies ... ERROR ``` - installed size is 7.5Mb - sub-directories of 1Mb or more: - R 3.0Mb - doc 3.6Mb + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # ChromSCape @@ -448,53 +554,73 @@ Run `revdep_details(, "ChromSCape")` for more info ## In both -* checking for hidden files and directories ... NOTE - ``` - Found the following hidden files and directories: - .BBSoptions - These were most likely included in error. See section ‘Package - structure’ in the ‘Writing R Extensions’ manual. - ``` - -* checking installed package size ... NOTE +* checking whether package ‘ChromSCape’ can be installed ... ERROR ``` - installed size is 8.2Mb - sub-directories of 1Mb or more: - data 1.4Mb - doc 2.9Mb - www 2.0Mb + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00install.out’ for details. ``` -* checking R code for possible problems ... NOTE +* checking package dependencies ... NOTE ``` - bams_to_matrix_indexes: no visible binding for global variable - ‘files_dir_list’ - enrich_TF_ChEA3_genes: no visible binding for global variable - ‘CheA3_TF_nTargets’ - filter_correlated_cell_scExp: no visible binding for global variable - ‘run_tsne’ - generate_analysis: no visible binding for global variable ‘k’ - generate_analysis: no visible binding for global variable - ‘clusterConsensus’ - get_most_variable_cyto: no visible binding for global variable - ... - plot_top_TF_scExp: no visible binding for global variable ‘TF’ - rebin_matrix: no visible binding for global variable ‘new_row’ - rebin_matrix: no visible binding for global variable ‘origin_value’ - subset_bam_call_peaks: no visible binding for global variable - ‘merged_bam’ - Undefined global functions or variables: - CheA3_TF_nTargets Component Fri_cyto Gain_or_Loss Gene TF V1 V2 - absolute_value cluster clusterConsensus cytoBand files_dir_list genes - group k merged_bam molecule ncells new_row orientation origin_value - percent_active run_tsne sample_id total_counts + Package suggested but not available for checking: ‘igraph’ ``` -* checking Rd files ... NOTE +* checking for hidden files and directories ... NOTE ``` - prepare_Rd: raw_counts_to_sparse_matrix.Rd:6-8: Dropping empty section \source + Found the following hidden files and directories: + .BBSoptions + These were most likely included in error. See section ‘Package + structure’ in the ‘Writing R Extensions’ manual. ``` +## Installation + +### Devel + +``` +* installing *source* package ‘ChromSCape’ ... +** using staged installation +** libs +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o +g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘ChromSCape’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/ChromSCape’ + + +``` +### CRAN + +``` +* installing *source* package ‘ChromSCape’ ... +** using staged installation +** libs +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o +g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘ChromSCape’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/ChromSCape’ + + +``` # civis
@@ -615,6 +741,30 @@ Run `revdep_details(, "DeclareDesign")` for more info Package suggested but not available for checking: ‘DesignLibrary’ ``` +# delayed + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/tlverse/delayed +* Source code: https://github.com/cran/delayed +* Date/Publication: 2022-10-19 22:25:09 UTC +* Number of recursive dependencies: 80 + +Run `revdep_details(, "delayed")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + # dipsaus
@@ -696,10 +846,36 @@ Run `revdep_details(, "dragon")` for more info ## In both -* checking dependencies in R code ... NOTE +* checking package dependencies ... ERROR ``` - Namespace in Imports field not imported from: ‘htmltools’ - All declared Imports should be used. + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + +# drake + +
+ +* Version: 7.13.4 +* GitHub: https://github.com/ropensci/drake +* Source code: https://github.com/cran/drake +* Date/Publication: 2022-08-19 15:40:02 UTC +* Number of recursive dependencies: 162 + +Run `revdep_details(, "drake")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # EFAtools @@ -754,6 +930,35 @@ Run `revdep_details(, "envi")` for more info See ‘/c4/home/henrik/repositories/future/revdep/checks/envi/new/envi.Rcheck/00install.out’ for details. ``` +# EpiNow2 + +
+ +* Version: 1.3.4 +* GitHub: https://github.com/epiforecasts/EpiNow2 +* Source code: https://github.com/cran/EpiNow2 +* Date/Publication: 2023-02-12 21:52:20 UTC +* Number of recursive dependencies: 128 + +Run `revdep_details(, "EpiNow2")` for more info + +
+ +## In both + +* checking installed package size ... NOTE + ``` + installed size is 229.4Mb + sub-directories of 1Mb or more: + help 1.4Mb + libs 227.2Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + # epitweetr
@@ -827,18 +1032,12 @@ Run `revdep_details(, "flowGraph")` for more info ## In both -* checking R code for possible problems ... NOTE - ``` - get_child: no visible binding for global variable ‘no_cores’ - get_paren: no visible binding for global variable ‘no_cores’ - ms_psig: no visible binding for global variable ‘meta’ - Undefined global functions or variables: - meta no_cores +* checking package dependencies ... ERROR ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘doParallel’ + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # foieGras @@ -886,6 +1085,30 @@ Run `revdep_details(, "forecastML")` for more info All declared Imports should be used. ``` +# genBaRcode + +
+ +* Version: 1.2.5 +* GitHub: NA +* Source code: https://github.com/cran/genBaRcode +* Date/Publication: 2022-05-27 12:50:05 UTC +* Number of recursive dependencies: 158 + +Run `revdep_details(, "genBaRcode")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + # geocmeans
@@ -971,6 +1194,11 @@ Run `revdep_details(, "greed")` for more info ## In both +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘igraph’ + ``` + * checking installed package size ... NOTE ``` installed size is 36.8Mb @@ -1044,42 +1272,6 @@ Run `revdep_details(, "hackeRnews")` for more info ## In both -* checking examples ... ERROR - ``` - Running examples in ‘hackeRnews-Ex.R’ failed - The error most likely occurred in: - - > ### Name: get_best_stories - > ### Title: Hacker News best stories - > ### Aliases: get_best_stories - > - > ### ** Examples - > - > # get the best story on Hacker News - > best_story <- get_best_stories(max_items = 1) - Error in curl::curl_fetch_memory(url, handle = handle) : - Received HTTP code 503 from proxy after CONNECT - Calls: get_best_stories ... request_fetch -> request_fetch.write_memory -> - Execution halted - ``` - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘hackeRnews-specs.Rmd’ using rmarkdown - Quitting from lines 43-45 (hackeRnews-specs.Rmd) - Error: processing vignette 'hackeRnews-specs.Rmd' failed with diagnostics: - Received HTTP code 503 from proxy after CONNECT - --- failed re-building ‘hackeRnews-specs.Rmd’ - - SUMMARY: processing the following file failed: - ‘hackeRnews-specs.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - * checking LazyData ... NOTE ``` 'LazyData' is specified without a 'data' directory @@ -1152,17 +1344,12 @@ Run `revdep_details(, "infercnv")` for more info ## In both -* checking installed package size ... NOTE - ``` - installed size is 5.1Mb - sub-directories of 1Mb or more: - extdata 3.1Mb - ``` - -* checking dependencies in R code ... NOTE +* checking package dependencies ... ERROR ``` - Unexported object imported by a ':::' call: ‘HiddenMarkov:::makedensity’ - See the note in ?`:::` about the use of this operator. + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # inlinedocs @@ -1394,6 +1581,27 @@ Run `revdep_details(, "keyATM")` for more info libs 23.6Mb ``` +# lava + +
+ +* Version: 1.7.1 +* GitHub: https://github.com/kkholst/lava +* Source code: https://github.com/cran/lava +* Date/Publication: 2023-01-06 22:30:34 UTC +* Number of recursive dependencies: 136 + +Run `revdep_details(, "lava")` for more info + +
+ +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘igraph’ + ``` + # lidR
@@ -1437,32 +1645,28 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’ + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 60963 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + ERROR Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - 3. └─lidR (local) algorithm(st_bbox(las)) - 4. └─lidR:::crop_special_its(treetops, chm, bbox) - 5. └─lidR:::raster_crop(chm, bbox) - 6. ├─sf::st_crop(raster, bbox) - 7. └─stars:::st_crop.stars(raster, bbox) - ── Error ('test-segment_trees.R:147'): Silva algorithm works with sfc ────────── - ... - 7. └─lidR:::segment_trees.LAS(las, silva2016(chm, ttops_shifted500)) - 8. └─lidR (local) algorithm(st_bbox(las)) - 9. └─lidR:::crop_special_its(treetops, chm, bbox) - 10. └─lidR:::raster_crop(chm, bbox) - 11. ├─sf::st_crop(raster, bbox) - 12. └─stars:::st_crop.stars(raster, bbox) - - [ FAIL 20 | WARN 3 | SKIP 40 | PASS 1357 ] - Error: Test failures - Execution halted + Complete output: + > Sys.setenv("R_TESTS" = "") + > + > library(testthat) + > library(lidR) + > test_check("lidR") + Tests using raster: terra + Tests using future: TRUE + Tests using OpenMP thread: 32 + OGR: Unsupported geometry type + OGR: Unsupported geometry type + terminate called after throwing an instance of 'std::length_error' + what(): basic_string::_S_create ``` * checking installed package size ... NOTE ``` - installed size is 19.7Mb + installed size is 19.6Mb sub-directories of 1Mb or more: R 1.2Mb extdata 1.1Mb @@ -1604,6 +1808,30 @@ Run `revdep_details(, "microservices")` for more info Execution halted ``` +# migraph + +
+ +* Version: 0.13.2 +* GitHub: https://github.com/snlab-ch/migraph +* Source code: https://github.com/cran/migraph +* Date/Publication: 2022-12-20 16:20:02 UTC +* Number of recursive dependencies: 137 + +Run `revdep_details(, "migraph")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + # MineICA
@@ -1620,58 +1848,12 @@ Run `revdep_details(, "MineICA")` for more info ## In both -* checking dependencies in R code ... WARNING - ``` - Namespace in Imports field not imported from: ‘lumiHumanAll.db’ - All declared Imports should be used. - Packages in Depends field not imported from: - ‘GOstats’ ‘Hmisc’ ‘JADE’ ‘RColorBrewer’ ‘Rgraphviz’ ‘annotate’ - ‘biomaRt’ ‘cluster’ ‘colorspace’ ‘fastICA’ ‘foreach’ ‘ggplot2’ - ‘graph’ ‘gtools’ ‘igraph’ ‘marray’ ‘mclust’ ‘methods’ ‘plyr’ ‘scales’ - ‘xtable’ - These packages need to be imported from (in the NAMESPACE file) - for when this namespace is loaded but not attached. - Missing or unexported object: ‘GOstats::geneIdsByCategory’ - ':::' calls which should be '::': - ‘Biobase:::annotation<-’ ‘Biobase:::validMsg’ ‘fpc:::pamk’ - ‘lumi:::getChipInfo’ ‘mclust:::adjustedRandIndex’ - See the note in ?`:::` about the use of this operator. - Unexported object imported by a ':::' call: ‘Biobase:::isValidVersion’ - See the note in ?`:::` about the use of this operator. - ``` - -* checking Rd cross-references ... WARNING +* checking package dependencies ... ERROR ``` - Missing link or links in documentation object 'Alist.Rd': - ‘class-IcaSet’ + Package required but not available: ‘igraph’ - Missing link or links in documentation object 'Slist.Rd': - ‘class-IcaSet’ + Package suggested but not available for checking: ‘igraph’ - Missing link or links in documentation object 'class-IcaSet.Rd': - ‘class-IcaSet’ - - Missing link or links in documentation object 'getComp.Rd': - ‘class-IcaSet’ - - Missing link or links in documentation object 'runAn.Rd': - ‘[Category:class-GOHyperGParams]{GOHyperGParams}’ - - See section 'Cross-references' in the 'Writing R Extensions' manual. - ``` - -* checking for missing documentation entries ... WARNING - ``` - Undocumented S4 classes: - ‘MineICAParams’ - All user-level objects in a package (including S4 classes and methods) - should have documentation entries. - See chapter ‘Writing R documentation files’ in the ‘Writing R - Extensions’ manual. - ``` - -* checking package dependencies ... NOTE - ``` Package which this enhances but not available for checking: ‘doMC’ Depends: includes the non-default packages: @@ -1681,86 +1863,200 @@ Run `revdep_details(, "MineICA")` for more info 'graph', 'annotate', 'Hmisc', 'fastICA', 'JADE' Adding so many packages to the search path is excessive and importing selectively is preferable. + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + +# missSBM + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/grossSBM/missSBM +* Source code: https://github.com/cran/missSBM +* Date/Publication: 2022-08-23 12:10:06 UTC +* Number of recursive dependencies: 109 + +Run `revdep_details(, "missSBM")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + +# mistyR + +
+ +* Version: 1.6.0 +* GitHub: https://github.com/saezlab/mistyR +* Source code: https://github.com/cran/mistyR +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 152 + +Run `revdep_details(, "mistyR")` for more info -* checking DESCRIPTION meta-information ... NOTE +
+ +## In both + +* checking examples ... ERROR ``` - Packages listed in more than one of Depends, Imports, Suggests, Enhances: - ‘biomaRt’ ‘GOstats’ ‘cluster’ ‘mclust’ ‘igraph’ - A package should be listed in only one of these fields. + Running examples in ‘mistyR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_interaction_communities + > ### Title: Plot marker interaction communities + > ### Aliases: plot_interaction_communities + > + > ### ** Examples + > + > all.samples <- list.dirs("results", recursive = FALSE) + ... + + Collecting importances + + Aggregating + > + > misty.results %>% + + plot_interaction_communities("intra") %>% + + plot_interaction_communities("para.10") + Error: The provided result list is malformed. Consider using collect_results(). + Execution halted ``` -* checking R code for possible problems ... NOTE +* checking tests ... ``` - addGenesToGoReport: no visible global function definition for - ‘conditional’ - addGenesToGoReport: no visible global function definition for - ‘sigCategories’ - annot2Color: no visible global function definition for ‘brewer.pal’ - annot2Color: no visible global function definition for ‘heat_hcl’ - annot2Color: no visible global function definition for ‘terrain_hcl’ - annot2Color: no visible global function definition for ‘cm.colors’ - annot2Color: no visible global function definition for ‘rainbow_hcl’ - annotFeatures: no visible global function definition for ‘na.omit’ + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + + Computing triangulation + + Generating juxtaview + + Generating paraview ... - importFrom("methods", "callNextMethod", "new", "validObject") - importFrom("stats", "aggregate", "as.dendrogram", "as.dist", - "as.hclust", "chisq.test", "cor", "cor.test", "cutree", - "dist", "hclust", "kmeans", "kruskal.test", "lm", "median", - "na.omit", "order.dendrogram", "p.adjust", "quantile", - "reorder", "shapiro.test", "wilcox.test") - importFrom("utils", "capture.output", "combn", "read.table", - "write.table") - to your NAMESPACE file (and ensure that your DESCRIPTION Imports field - contains 'methods'). + 1. ├─testthat::expect_invisible(...) at test-plots.R:47:2 + 2. │ └─base::withVisible(call) + 3. ├─base::suppressWarnings(...) + 4. │ └─base::withCallingHandlers(...) + 5. └─mistyR::plot_interaction_communities(...) + 6. └─assertthat::assert_that(...) + + [ FAIL 1 | WARN 74 | SKIP 0 | PASS 172 ] + Error: Test failures + Execution halted ``` -* checking re-building of vignette outputs ... NOTE +* checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: - --- re-building ‘MineICA.Rnw’ using Sweave - Loading required package: BiocGenerics - - Attaching package: ‘BiocGenerics’ - - The following objects are masked from ‘package:stats’: - - IQR, mad, sd, var, xtabs + --- re-building ‘mistyR.Rmd’ using rmarkdown + The magick package is required to crop "/c4/home/henrik/repositories/future/revdep/checks/mistyR/new/mistyR.Rcheck/vign_test/mistyR/vignettes/mistyR_files/figure-html/unnamed-chunk-2-1.png" but not available. + Progress: ─────────────────────────────────────────────────────────────── 100% + Progress: ─────────────────────────────────────────────────────────────── 100% + Progress: ─────────────────────────────────────────────────────────────── 100% + Progress: ─────────────────────────────────────────────────────────────── 100% + Progress: ─────────────────────────────────────────────────────────────── 100% + Progress: ─────────────────────────────────────────────────────────────── 100% ... - l.23 \usepackage - {subfig}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘MineICA.Rnw’ + Quitting from lines 251-252 (mistyR.Rmd) + Error: processing vignette 'mistyR.Rmd' failed with diagnostics: + The package igraph (>= 1.2.7) is required to calculate the interaction communities. + --- failed re-building ‘mistyR.Rmd’ SUMMARY: processing the following file failed: - ‘MineICA.Rnw’ + ‘mistyR.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# missSBM +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘igraph’ + ``` + +# mlr3pipelines
-* Version: 1.0.3 -* GitHub: https://github.com/grossSBM/missSBM -* Source code: https://github.com/cran/missSBM -* Date/Publication: 2022-08-23 12:10:06 UTC -* Number of recursive dependencies: 109 +* Version: 0.4.2 +* GitHub: https://github.com/mlr-org/mlr3pipelines +* Source code: https://github.com/cran/mlr3pipelines +* Date/Publication: 2022-09-20 22:00:07 UTC +* Number of recursive dependencies: 159 -Run `revdep_details(, "missSBM")` for more info +Run `revdep_details(, "mlr3pipelines")` for more info
## In both -* checking installed package size ... NOTE +* checking examples ... ERROR ``` - installed size is 9.7Mb - sub-directories of 1Mb or more: - libs 7.8Mb + Running examples in ‘mlr3pipelines-Ex.R’ failed + The error most likely occurred in: + + > ### Name: mlr_pipeops_imputelearner + > ### Title: Impute Features by Fitting a Learner + > ### Aliases: mlr_pipeops_imputelearner PipeOpImputeLearner + > + > ### ** Examples + > + > library("mlr3") + ... + Empty data.table (0 rows and 8 cols): .impute_col,age,glucose,insulin,pedigree,pregnant... + + $task_prototype + Empty data.table (0 rows and 8 cols): .impute_col,age,glucose,insulin,pedigree,pregnant... + + $mlr3_version + [1] ‘0.14.1’ + + $train_task + (768 x 8) + ``` + +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + Starting 2 test processes + [ FAIL 5 | WARN 0 | SKIP 79 | PASS 12709 ] + + ══ Skipped tests ═══════════════════════════════════════════════════════════════ + • On CRAN (77) + • empty test (2) + ... + Error: The following packages could not be loaded: igraph + Backtrace: + ▆ + 1. └─graph$plot() at test_multichannels.R:100:2 + 2. └─mlr3pipelines:::.__Graph__plot(...) + 3. └─mlr3misc::require_namespaces("igraph") + + [ FAIL 5 | WARN 0 | SKIP 79 | PASS 12709 ] + Error: Test failures + Execution halted + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘igraph’ ``` # momentuHMM @@ -1820,6 +2116,54 @@ Run `revdep_details(, "mslp")` for more info Execution halted ``` +# netShiny + +
+ +* Version: 1.0 +* GitHub: NA +* Source code: https://github.com/cran/netShiny +* Date/Publication: 2022-08-22 09:30:02 UTC +* Number of recursive dependencies: 151 + +Run `revdep_details(, "netShiny")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + +# nncc + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/nncc +* Date/Publication: 2022-08-30 13:00:02 UTC +* Number of recursive dependencies: 82 + +Run `revdep_details(, "nncc")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + # oncomsm
@@ -1849,39 +2193,6 @@ Run `revdep_details(, "oncomsm")` for more info GNU make is a SystemRequirements. ``` -# onemapsgapi - -
- -* Version: 1.1.0 -* GitHub: NA -* Source code: https://github.com/cran/onemapsgapi -* Date/Publication: 2022-11-29 08:00:03 UTC -* Number of recursive dependencies: 70 - -Run `revdep_details(, "onemapsgapi")` for more info - -
- -## In both - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘onemapsgapi_vignette.Rmd’ using rmarkdown - Quitting from lines 36-37 (onemapsgapi_vignette.Rmd) - Error: processing vignette 'onemapsgapi_vignette.Rmd' failed with diagnostics: - Received HTTP code 503 from proxy after CONNECT - --- failed re-building ‘onemapsgapi_vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘onemapsgapi_vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # OOS
@@ -1898,23 +2209,6 @@ Run `revdep_details(, "OOS")` for more info ## In both -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘basic_introduction.Rmd’ using rmarkdown - Quitting from lines 31-49 (basic_introduction.Rmd) - Error: processing vignette 'basic_introduction.Rmd' failed with diagnostics: - object 'UNRATE' not found - --- failed re-building ‘basic_introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘basic_introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - * checking LazyData ... NOTE ``` 'LazyData' is specified without a 'data' directory @@ -1952,17 +2246,41 @@ Run `revdep_details(, "partR2")` for more info * Date/Publication: 2022-08-16 13:00:20 UTC * Number of recursive dependencies: 92 -Run `revdep_details(, "pavo")` for more info +Run `revdep_details(, "pavo")` for more info + +
+ +## In both + +* checking whether package ‘pavo’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: no DISPLAY variable so Tk is not available + See ‘/c4/home/henrik/repositories/future/revdep/checks/pavo/new/pavo.Rcheck/00install.out’ for details. + ``` + +# pGRN + +
+ +* Version: 0.3.5 +* GitHub: NA +* Source code: https://github.com/cran/pGRN +* Date/Publication: 2023-01-17 17:20:02 UTC +* Number of recursive dependencies: 93 + +Run `revdep_details(, "pGRN")` for more info
## In both -* checking whether package ‘pavo’ can be installed ... WARNING +* checking package dependencies ... ERROR ``` - Found the following significant warnings: - Warning: no DISPLAY variable so Tk is not available - See ‘/c4/home/henrik/repositories/future/revdep/checks/pavo/new/pavo.Rcheck/00install.out’ for details. + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # photosynthesis @@ -2018,10 +2336,10 @@ Run `revdep_details(, "phylolm")` for more info
-* Version: 1.0.0 +* Version: 1.0.1 * GitHub: https://github.com/pln-team/PLNmodels * Source code: https://github.com/cran/PLNmodels -* Date/Publication: 2023-01-06 13:20:06 UTC +* Date/Publication: 2023-02-12 14:42:07 UTC * Number of recursive dependencies: 146 Run `revdep_details(, "PLNmodels")` for more info @@ -2030,12 +2348,12 @@ Run `revdep_details(, "PLNmodels")` for more info ## In both -* checking installed package size ... NOTE +* checking package dependencies ... ERROR ``` - installed size is 21.7Mb - sub-directories of 1Mb or more: - doc 2.1Mb - libs 18.3Mb + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # portvine @@ -2131,6 +2449,48 @@ Run `revdep_details(, "prewas")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + 5. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 6. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) + 7. └─base (local) withOneRestart(expr, restarts[[1L]]) + 8. └─base (local) doWithOneRestart(return(expr), restart) + ── Error ('test-preprocess_tree_and_vcf.R:46'): root_tree roots tree and drops outgroup when given valid inputs ── + + ... + 2. ├─base::namespaceImportFrom(...) + 3. │ └─base::asNamespace(ns) + 4. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 5. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) + 6. └─base (local) withOneRestart(expr, restarts[[1L]]) + 7. └─base (local) doWithOneRestart(return(expr), restart) + + [ FAIL 4 | WARN 15 | SKIP 0 | PASS 324 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘getting_started_with_prewas.Rmd’ using rmarkdown + Quitting from lines 195-198 (getting_started_with_prewas.Rmd) + Error: processing vignette 'getting_started_with_prewas.Rmd' failed with diagnostics: + there is no package called 'igraph' + --- failed re-building ‘getting_started_with_prewas.Rmd’ + + SUMMARY: processing the following file failed: + ‘getting_started_with_prewas.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + * checking dependencies in R code ... NOTE ``` Namespace in Imports field not imported from: ‘stats’ @@ -2141,11 +2501,11 @@ Run `revdep_details(, "prewas")` for more info
-* Version: 2.3.0 +* Version: 2.4.0 * GitHub: https://github.com/stan-dev/projpred * Source code: https://github.com/cran/projpred -* Date/Publication: 2023-01-10 15:00:03 UTC -* Number of recursive dependencies: 143 +* Date/Publication: 2023-02-12 13:30:02 UTC +* Number of recursive dependencies: 149 Run `revdep_details(, "projpred")` for more info @@ -2153,6 +2513,21 @@ Run `revdep_details(, "projpred")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(projpred) + This is projpred version 2.4.0. + > + > test_check("projpred") + Error: Package "rstanarm" is needed for these tests. Please install it. + Execution halted + ``` + * checking package dependencies ... NOTE ``` Package suggested but not available for checking: ‘cmdstanr’ @@ -2179,6 +2554,85 @@ Run `revdep_details(, "promises")` for more info 'LazyData' is specified without a 'data' directory ``` +# Prostar + +
+ +* Version: 1.30.5 +* GitHub: https://github.com/prostarproteomics/Prostar +* Source code: https://github.com/cran/Prostar +* Date/Publication: 2023-02-10 +* Number of recursive dependencies: 166 + +Run `revdep_details(, "Prostar")` for more info + +
+ +## In both + +* checking whether package ‘Prostar’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Prostar’ ... +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Prostar’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/Prostar’ + + +``` +### CRAN + +``` +* installing *source* package ‘Prostar’ ... +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Prostar’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/old/Prostar.Rcheck/Prostar’ + + +``` +# protti + +
+ +* Version: 0.6.0 +* GitHub: https://github.com/jpquast/protti +* Source code: https://github.com/cran/protti +* Date/Publication: 2023-01-20 10:30:02 UTC +* Number of recursive dependencies: 195 + +Run `revdep_details(, "protti")` for more info + +
+ +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘igraph’ + ``` + # QDNAseq
@@ -2243,67 +2697,47 @@ Run `revdep_details(, "RAINBOWR")` for more info libs 36.5Mb ``` -# regmedint +# rangeMapper
-* Version: 1.0.0 -* GitHub: https://github.com/kaz-yos/regmedint -* Source code: https://github.com/cran/regmedint -* Date/Publication: 2022-04-06 20:20:02 UTC -* Number of recursive dependencies: 134 +* Version: 2.0.3 +* GitHub: https://github.com/mpio-be/rangeMapper +* Source code: https://github.com/cran/rangeMapper +* Date/Publication: 2022-10-03 22:20:02 UTC +* Number of recursive dependencies: 113 -Run `revdep_details(, "regmedint")` for more info +Run `revdep_details(, "rangeMapper")` for more info
## In both -* checking dependencies in R code ... NOTE +* checking package dependencies ... NOTE ``` - Namespace in Imports field not imported from: ‘Deriv’ - All declared Imports should be used. + Package suggested but not available for checking: ‘igraph’ ``` -# reproducible +# regmedint
-* Version: 1.2.16 -* GitHub: https://github.com/PredictiveEcology/reproducible -* Source code: https://github.com/cran/reproducible -* Date/Publication: 2022-12-22 09:50:02 UTC -* Number of recursive dependencies: 104 +* Version: 1.0.0 +* GitHub: https://github.com/kaz-yos/regmedint +* Source code: https://github.com/cran/regmedint +* Date/Publication: 2022-04-06 20:20:02 UTC +* Number of recursive dependencies: 134 -Run `revdep_details(, "reproducible")` for more info +Run `revdep_details(, "regmedint")` for more info
## In both -* checking tests ... +* checking dependencies in R code ... NOTE ``` - Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 7156 Segmentation fault ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 - - ERROR - Running the tests in ‘tests/test-all.R’ failed. - Last 50 lines of output: - adding: scratch/henrik/RtmpcbGlaK/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) - adding: scratch/henrik/RtmpcbGlaK/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) - - *** caught segfault *** - address 0x40, cause 'memory not mapped' - ... - 36: doTryCatch(return(expr), name, parentenv, handler) - 37: tryCatchOne(expr, names, parentenv, handlers[[1L]]) - 38: tryCatchList(expr, classes, parentenv, handlers) - 39: tryCatch(code, testthat_abort_reporter = function(cnd) { cat(conditionMessage(cnd), "\n") NULL}) - 40: with_reporter(reporters$multi, lapply(test_paths, test_one_file, env = env, wrap = wrap)) - 41: test_files_serial(test_dir = test_dir, test_package = test_package, test_paths = test_paths, load_helpers = load_helpers, reporter = reporter, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package) - 42: test_files(test_dir = path, test_paths = test_paths, test_package = package, reporter = reporter, load_helpers = load_helpers, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package, parallel = parallel) - 43: test_dir("testthat", package = package, reporter = reporter, ..., load_package = "installed") - 44: test_check("reproducible") - An irrecoverable exception occurred. R is aborting now ... + Namespace in Imports field not imported from: ‘Deriv’ + All declared Imports should be used. ``` # rgee @@ -2383,6 +2817,66 @@ Run `revdep_details(, "sapfluxnetr")` for more info Note: found 4 marked UTF-8 strings ``` +# scBubbletree + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/snaketron/scBubbletree +* Source code: https://github.com/cran/scBubbletree +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 178 + +Run `revdep_details(, "scBubbletree")` for more info + +
+ +## In both + +* checking whether package ‘scBubbletree’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘scBubbletree’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘scBubbletree’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/scBubbletree’ + + +``` +### CRAN + +``` +* installing *source* package ‘scBubbletree’ ... +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘scBubbletree’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/old/scBubbletree.Rcheck/scBubbletree’ + + +``` # scDiffCom
@@ -2399,6 +2893,36 @@ Run `revdep_details(, "scDiffCom")` for more info ## In both +* checking tests ... + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(scDiffCom) + > + > test_check("scDiffCom") + Loading required package: SeuratObject + ... + 6. ├─base::namespaceImportFrom(...) + 7. │ └─base::asNamespace(ns) + 8. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 9. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) + 10. └─base (local) withOneRestart(expr, restarts[[1L]]) + 11. └─base (local) doWithOneRestart(return(expr), restart) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 6 ] + Error: Test failures + Execution halted + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘igraph’ + ``` + * checking dependencies in R code ... NOTE ``` Namespaces in Imports field not imported from: @@ -2498,31 +3022,6 @@ Run `revdep_details(, "sentopics")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > - > library("testthat") - > library("sentopics") - > - > if (Sys.getenv("R_COVR") != "true") { - + test_check("sentopics") - ... - Backtrace: - ▆ - 1. └─sentopics:::get_ECB_press_conferences(years = 1998) at test-others.R:2:2 - 2. └─base::lapply(...) - 3. └─sentopics (local) FUN(X[[i]], ...) - 4. └─utils::download.file(...) - - [ FAIL 1 | WARN 2 | SKIP 1 | PASS 321 ] - Error: Test failures - Execution halted - ``` - * checking installed package size ... NOTE ``` installed size is 8.0Mb @@ -2557,17 +3056,12 @@ Run `revdep_details(, "Seurat")` for more info ## In both -* checking installed package size ... NOTE - ``` - installed size is 14.5Mb - sub-directories of 1Mb or more: - R 1.4Mb - libs 12.4Mb - ``` - -* checking Rd cross-references ... NOTE +* checking package dependencies ... ERROR ``` - Package unavailable to check Rd xrefs: ‘Signac’ + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # SeuratObject @@ -2659,54 +3153,68 @@ Run `revdep_details(, "signeR")` for more info ## In both -* checking installed package size ... NOTE - ``` - installed size is 6.6Mb - sub-directories of 1Mb or more: - R 1.1Mb - doc 4.6Mb - ``` - -* checking R code for possible problems ... NOTE - ``` - covariate: no visible binding for global variable ‘.’ - denovo: no visible binding for global variable - ‘BSgenome.Hsapiens.UCSC.hg19’ - denovo: no visible binding for global variable - ‘BSgenome.Hsapiens.UCSC.hg38’ - explorepage: no visible binding for global variable ‘.’ - fitting: no visible binding for global variable - ‘BSgenome.Hsapiens.UCSC.hg19’ - fitting: no visible binding for global variable - ‘BSgenome.Hsapiens.UCSC.hg38’ - ... - ExposureCorrelation,SignExp-numeric: no visible binding for global - variable ‘exposure’ - ExposureCorrelation,matrix-numeric: no visible binding for global - variable ‘Feature’ - ExposureCorrelation,matrix-numeric: no visible binding for global - variable ‘exposure’ - Undefined global functions or variables: - . BSgenome.Hsapiens.UCSC.hg19 BSgenome.Hsapiens.UCSC.hg38 Col Feature - Frequency Row Samples Signatures alt<- exposure fc project sig - sig_test - ``` - -* checking Rd files ... NOTE - ``` - prepare_Rd: cosmic_data.Rd:91-93: Dropping empty section \details - prepare_Rd: cosmic_data.Rd:98-100: Dropping empty section \references - prepare_Rd: cosmic_data.Rd:101-102: Dropping empty section \examples - prepare_Rd: tcga_similarities.Rd:96-98: Dropping empty section \details - prepare_Rd: tcga_similarities.Rd:99-101: Dropping empty section \source - prepare_Rd: tcga_similarities.Rd:102-104: Dropping empty section \references - prepare_Rd: tcga_similarities.Rd:105-106: Dropping empty section \examples - prepare_Rd: tcga_tumors.Rd:18-20: Dropping empty section \details - prepare_Rd: tcga_tumors.Rd:21-23: Dropping empty section \source - prepare_Rd: tcga_tumors.Rd:24-26: Dropping empty section \references - prepare_Rd: tcga_tumors.Rd:27-28: Dropping empty section \examples - ``` - +* checking whether package ‘signeR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘signeR’ ... +** using staged installation +** libs +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o +g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs +** R +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘signeR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/signeR’ + + +``` +### CRAN + +``` +* installing *source* package ‘signeR’ ... +** using staged installation +** libs +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o +g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o +g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR +installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs +** R +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘signeR’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/signeR’ + + +``` # SimDesign
@@ -2774,11 +3282,12 @@ Run `revdep_details(, "solitude")` for more info ## In both -* checking dependencies in R code ... NOTE +* checking package dependencies ... ERROR ``` - Namespaces in Imports field not imported from: - ‘R6’ ‘lgr’ - All declared Imports should be used. + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # spaMM @@ -2914,6 +3423,30 @@ Run `revdep_details(, "spatialwarnings")` for more info libs 5.8Mb ``` +# specr + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/masurp/specr +* Source code: https://github.com/cran/specr +* Date/Publication: 2023-01-20 13:50:02 UTC +* Number of recursive dependencies: 149 + +Run `revdep_details(, "specr")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + # sphunif
@@ -2958,13 +3491,12 @@ Run `revdep_details(, "spNetwork")` for more info ## In both -* checking installed package size ... NOTE +* checking package dependencies ... ERROR ``` - installed size is 25.2Mb - sub-directories of 1Mb or more: - doc 1.0Mb - extdata 2.6Mb - libs 20.3Mb + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # squat @@ -3121,6 +3653,66 @@ Run `revdep_details(, "tableschema.r")` for more info Package unavailable to check Rd xrefs: ‘parsedate’ ``` +# tarchetypes + +
+ +* Version: 0.7.4 +* GitHub: https://github.com/ropensci/tarchetypes +* Source code: https://github.com/cran/tarchetypes +* Date/Publication: 2023-01-06 18:50:20 UTC +* Number of recursive dependencies: 78 + +Run `revdep_details(, "tarchetypes")` for more info + +
+ +## In both + +* checking whether package ‘tarchetypes’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘tarchetypes’ ... +** package ‘tarchetypes’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘tarchetypes’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/tarchetypes’ + + +``` +### CRAN + +``` +* installing *source* package ‘tarchetypes’ ... +** package ‘tarchetypes’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘tarchetypes’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/old/tarchetypes.Rcheck/tarchetypes’ + + +``` # targeted
@@ -3144,6 +3736,30 @@ Run `revdep_details(, "targeted")` for more info libs 15.7Mb ``` +# targets + +
+ +* Version: 0.14.2 +* GitHub: https://github.com/ropensci/targets +* Source code: https://github.com/cran/targets +* Date/Publication: 2023-01-06 14:50:02 UTC +* Number of recursive dependencies: 173 + +Run `revdep_details(, "targets")` for more info + +
+ +## In both + +* checking package dependencies ... ERROR + ``` + Package required but not available: ‘igraph’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. + ``` + # text
@@ -3181,39 +3797,68 @@ Run `revdep_details(, "TreeSearch")` for more info ## In both -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘custom.Rmd’ using rmarkdown - Error reading bibliography file ../inst/REFERENCES.bib: - (line 348, column 1): - unexpected '@' - Error: processing vignette 'custom.Rmd' failed with diagnostics: - pandoc document conversion failed with error 25 - --- failed re-building ‘custom.Rmd’ - - --- re-building ‘getting-started.Rmd’ using rmarkdown - ... - unexpected '@' - Error: processing vignette 'tree-search.Rmd' failed with diagnostics: - pandoc document conversion failed with error 25 - --- failed re-building ‘tree-search.Rmd’ - - SUMMARY: processing the following files failed: - ‘custom.Rmd’ ‘profile-scores.Rmd’ ‘profile.Rmd’ ‘tree-search.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -* checking installed package size ... NOTE - ``` - installed size is 6.3Mb - sub-directories of 1Mb or more: - datasets 1.6Mb - libs 2.4Mb - ``` - +* checking whether package ‘TreeSearch’ can be installed ... ERROR + ``` + Installation failed. + See ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘TreeSearch’ ... +** package ‘TreeSearch’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘TreeSearch’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/TreeSearch’ + + +``` +### CRAN + +``` +* installing *source* package ‘TreeSearch’ ... +** package ‘TreeSearch’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o +g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o +gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o +... +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘TreeSearch’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/old/TreeSearch.Rcheck/TreeSearch’ + + +``` # TriDimRegression
@@ -3355,13 +4000,54 @@ Run `revdep_details(, "vmeasur")` for more info ## In both -* checking whether package ‘vmeasur’ can be installed ... WARNING +* checking whether package ‘vmeasur’ can be installed ... ERROR ``` - Found the following significant warnings: - Warning: no DISPLAY variable so Tk is not available + Installation failed. See ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/00install.out’ for details. ``` +## Installation + +### Devel + +``` +* installing *source* package ‘vmeasur’ ... +** package ‘vmeasur’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘vmeasur’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/vmeasur’ + + +``` +### CRAN + +``` +* installing *source* package ‘vmeasur’ ... +** package ‘vmeasur’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘igraph’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘vmeasur’ +* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/old/vmeasur.Rcheck/vmeasur’ + + +``` # wru
From 2a18d7efc662c6e9fded9c5cf2edd8095a0a2c60 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 13 Feb 2023 12:07:52 -0800 Subject: [PATCH 54/88] DEPRECATION: multiprocess is now defunct in interactive mode and deprecated in batch mode [#546] --- DESCRIPTION | 2 +- NEWS.md | 6 +++++- R/options.R | 2 +- 3 files changed, 7 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 61c017ef..7eb60502 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9004 +Version: 1.31.0-9005 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NEWS.md b/NEWS.md index 299d3c72..bbaf510a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,7 +1,11 @@ # Version (development version) - * ... +## Deprecated and Defunct + * Deprecated `plan(multiprocess, ...)` is now defunct when running in + interactive mode. The next step is to make it defunct also when + running in batch mode. + # Version 1.31.0 [2023-01-31] diff --git a/R/options.R b/R/options.R index e12a0059..80900094 100644 --- a/R/options.R +++ b/R/options.R @@ -262,7 +262,7 @@ update_package_options <- function(debug = FALSE) { update_package_option("future.deprecated.ignore", split = ",", debug = debug) - update_package_option("future.deprecated.defunct", mode = "character", split = ",", debug = debug) + update_package_option("future.deprecated.defunct", mode = "character", split = ",", default = if (interactive()) "multiprocess" else NULL, debug = debug) update_package_option("future.fork.multithreading.enable", mode = "logical", debug = debug) From 557f026b355a5cd8374c514b92763cd672c4e992 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 13 Feb 2023 15:17:34 -0800 Subject: [PATCH 55/88] REVDEP: 279 revdep packages with 'multiprocess' being defunct in interactive mode [ci skip] --- revdep/README.md | 6 +++--- revdep/problems.md | 43 ++++++++++++++++++++++++++++++++++++++++++- 2 files changed, 45 insertions(+), 4 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 1b1a94c0..5a37e98b 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,14 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-12 | +|date |2023-02-13 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9004 |* | +|future |1.31.0 |1.31.0-9005 |* | |codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -248,7 +248,7 @@ |refineR |1.5.1 | | | | |[regmedint](problems.md#regmedint)|1.0.0 | | |1 | |remiod |1.0.2 | | | | -|reproducible |1.2.16 |-1 | | | +|[reproducible](problems.md#reproducible)|1.2.16 |1 | | | |reval |3.1-0 | | | | |[rgee](problems.md#rgee) |1.1.5 | | |2 | |[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | diff --git a/revdep/problems.md b/revdep/problems.md index 9a607eb7..f7a30019 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1645,7 +1645,7 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 60963 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 12039 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 ERROR Running the tests in ‘tests/testthat.R’ failed. @@ -2740,6 +2740,47 @@ Run `revdep_details(, "regmedint")` for more info All declared Imports should be used. ``` +# reproducible + +
+ +* Version: 1.2.16 +* GitHub: https://github.com/PredictiveEcology/reproducible +* Source code: https://github.com/cran/reproducible +* Date/Publication: 2022-12-22 09:50:02 UTC +* Number of recursive dependencies: 104 + +Run `revdep_details(, "reproducible")` for more info + +
+ +## In both + +* checking tests ... + ``` + Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 11278 Segmentation fault (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + + ERROR + Running the tests in ‘tests/test-all.R’ failed. + Last 50 lines of output: + adding: scratch/henrik/RtmprFW55G/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) + adding: scratch/henrik/RtmprFW55G/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) + + *** caught segfault *** + address 0x8, cause 'memory not mapped' + ... + 36: doTryCatch(return(expr), name, parentenv, handler) + 37: tryCatchOne(expr, names, parentenv, handlers[[1L]]) + 38: tryCatchList(expr, classes, parentenv, handlers) + 39: tryCatch(code, testthat_abort_reporter = function(cnd) { cat(conditionMessage(cnd), "\n") NULL}) + 40: with_reporter(reporters$multi, lapply(test_paths, test_one_file, env = env, wrap = wrap)) + 41: test_files_serial(test_dir = test_dir, test_package = test_package, test_paths = test_paths, load_helpers = load_helpers, reporter = reporter, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package) + 42: test_files(test_dir = path, test_paths = test_paths, test_package = package, reporter = reporter, load_helpers = load_helpers, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package, parallel = parallel) + 43: test_dir("testthat", package = package, reporter = reporter, ..., load_package = "installed") + 44: test_check("reproducible") + An irrecoverable exception occurred. R is aborting now ... + ``` + # rgee
From ae6f1376ff3c8106a32fc40a71924bcb60c15365 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 20 Feb 2023 22:04:22 +0100 Subject: [PATCH 56/88] Add optional assertion of the internal Future 'state' field [#667] --- DESCRIPTION | 2 +- NAMESPACE | 1 + NEWS.md | 2 ++ R/Future-class.R | 42 +++++++++++++++++++++++++++++++++++++----- R/options.R | 3 +++ 5 files changed, 44 insertions(+), 6 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 7eb60502..54cb91a8 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9005 +Version: 1.31.0-9006 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NAMESPACE b/NAMESPACE index 9ca1883d..9f53a36b 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,5 +1,6 @@ # Generated by roxygen2: do not edit by hand +S3method("$<-",Future) S3method("[",FutureGlobals) S3method("[",sessionDetails) S3method(as.FutureGlobals,FutureGlobals) diff --git a/NEWS.md b/NEWS.md index bbaf510a..c6178d56 100644 --- a/NEWS.md +++ b/NEWS.md @@ -2,6 +2,8 @@ ## Deprecated and Defunct + * Add optional assertion of the internal Future `state` field. + * Deprecated `plan(multiprocess, ...)` is now defunct when running in interactive mode. The next step is to make it defunct also when running in batch mode. diff --git a/R/Future-class.R b/R/Future-class.R index 210f7086..b116d358 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -176,12 +176,12 @@ Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdou ## /HB 2023-02-09 if (isTRUE(args$local) && Sys.getenv("R_FUTURE_CHECK_IGNORE_CIVIS", "true") == "true") { - for (call in sys.calls()) { - if ("CivisFuture" %in% as.character(call[[1]])) { + for (call in sys.calls()) { + if ("CivisFuture" %in% as.character(call[[1]])) { msg <- sprintf("%s. In this case it was because civis::CivisFuture() was used. Please contact the maintainers of the 'civis' package about this problem.", msg) - if (!interactive()) dfcn <- .Deprecated - break - } + if (!interactive()) dfcn <- .Deprecated + break + } } } @@ -820,6 +820,7 @@ getExpression.Future <- local({ } ## getExpression() }) + globals <- function(future, ...) UseMethod("globals") globals.Future <- function(future, ...) { @@ -831,3 +832,34 @@ packages <- function(future, ...) UseMethod("packages") packages.Future <- function(future, ...) { future[["packages"]] } + + +#' @export +`$<-.Future` <- function(x, name, value) { + if (name == "state") { + if (!is.element(value, c("created", "running", "finished", "failed", "interrupted"))) { + action <- getOption("future.state.onInvalid", "warning") + + ## FIXME: civis::CivisFuture uses 'succeeded' /HB 2019-06-18 + if (Sys.getenv("R_FUTURE_CHECK_IGNORE_CIVIS", "true") == "true") { + for (call in sys.calls()) { + if ("CivisFuture" %in% as.character(call[[1]])) { + action <- "ignore" + break + } + } + } + + if (action != "ignore") { + msg <- sprintf("Trying to assign an invalid value to the internal '%s' field of a %s object: %s", name, class(x)[1], value) + if (action == "error") { + stop(FutureError(msg, call = sys.call(), future = x)) + } else { + warning(FutureWarning(msg, call = sys.call(), future = x)) + } + } + } + } + + NextMethod() +} diff --git a/R/options.R b/R/options.R index 80900094..3ea6aa74 100644 --- a/R/options.R +++ b/R/options.R @@ -315,4 +315,7 @@ update_package_options <- function(debug = FALSE) { ## SETTINGS USED FOR DEPRECATING FEATURES ## future 1.22.0: update_package_option("future.globals.keepWhere", mode = "logical", debug = debug) + + ## future 1.32.0: + update_package_option("future.state.onInvalid", mode = "character", debug = debug) } From f4d0f22d9cffceed5950858108bd0edb99bae825 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 20 Feb 2023 17:12:03 -0800 Subject: [PATCH 57/88] FIX: new 'state' assignment operator failed to detect 'civis' --- DESCRIPTION | 2 +- R/Future-class.R | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 54cb91a8..2a4e6b1f 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9006 +Version: 1.31.0-9007 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/Future-class.R b/R/Future-class.R index b116d358..b7569626 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -843,7 +843,7 @@ packages.Future <- function(future, ...) { ## FIXME: civis::CivisFuture uses 'succeeded' /HB 2019-06-18 if (Sys.getenv("R_FUTURE_CHECK_IGNORE_CIVIS", "true") == "true") { for (call in sys.calls()) { - if ("CivisFuture" %in% as.character(call[[1]])) { + if (any(grepl("CivisFuture$", as.character(call[[1]])))) { action <- "ignore" break } From 97ecd13d4b827f0cba5527c464894eae98798bfd Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 20 Feb 2023 17:12:57 -0800 Subject: [PATCH 58/88] REVDEP: 280 revdep packages using new 'state' validator, with temporary 'civis' passthrough --- revdep/README.md | 33 +++++++++-------- revdep/cran.md | 2 +- revdep/failures.md | 18 ++++----- revdep/problems.md | 92 ++++++++++++++++++++-------------------------- 4 files changed, 66 insertions(+), 79 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 5a37e98b..c1397fdd 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,14 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-13 | +|date |2023-02-20 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9005 |* | +|future |1.31.0 |1.31.0-9007 |* | |codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -30,25 +30,25 @@ |package |version |error |warning |note | |:------------|:-------|:-----|:-------|:----| -|[AlpsNMR](failures.md#alpsnmr)|4.0.3 |1 | | | +|[AlpsNMR](failures.md#alpsnmr)|4.0.4 |1 | | | |[bayesian](failures.md#bayesian)|0.0.9 |1 | | | |[brms](failures.md#brms)|2.18.0 |1 | |1 | |[ChromSCape](failures.md#chromscape)|1.8.0 |1 | |2 | -|[Prostar](failures.md#prostar)|1.30.5 |1 | | | +|[Prostar](failures.md#prostar)|1.30.6 |1 | | | |[scBubbletree](failures.md#scbubbletree)|1.0.0 |1 | | | |[signeR](failures.md#signer)|2.0.2 |1 | | | |[tarchetypes](failures.md#tarchetypes)|0.7.4 |1 | | | -|[TreeSearch](failures.md#treesearch)|1.2.0 |1 | | | +|[TreeSearch](failures.md#treesearch)|1.3.0 |1 | | | |[vmeasur](failures.md#vmeasur)|0.1.4 |1 | | | -## All (279) +## All (280) |package |version |error |warning |note | |:------------------------|:---------|:-----|:-------|:----| |[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | |alookr |0.3.7 | | | | |alphaci |1.0.0 | | | | -|[AlpsNMR](failures.md#alpsnmr)|4.0.3 |1 | | | +|[AlpsNMR](failures.md#alpsnmr)|4.0.4 |1 | | | |arkdb |0.0.16 | | | | |aroma.affymetrix |3.2.1 | | | | |aroma.cn |1.7.0 | | | | @@ -98,14 +98,14 @@ |[drake](problems.md#drake)|7.13.4 |1 | | | |drimmR |1.0.1 | | | | |drtmle |1.1.2 | | | | -|dsos |0.1.1 | | | | +|dsos |0.1.2 | | | | |DT |0.27 | | | | |easyalluvial |0.3.1 | | | | |ecic |0.0.2 | | | | |[EFAtools](problems.md#efatools)|0.4.4 | | |2 | |elevatr |0.4.2 | | | | |[envi](problems.md#envi) |0.1.17 | |1 | | -|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | +|[EpiNow2](problems.md#epinow2)|1.3.4 |-1 | |2 | |[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | |epwshiftr |0.1.3 | | | | |ezcox |1.0.2 | | | | @@ -233,7 +233,7 @@ |progressr |0.13.0 | | | | |[projpred](problems.md#projpred)|2.4.0 |1 | |1 | |[promises](problems.md#promises)|1.2.0.1 | | |1 | -|[Prostar](failures.md#prostar)|1.30.5 |1 | | | +|[Prostar](failures.md#prostar)|1.30.6 |1 | | | |[protti](problems.md#protti)|0.6.0 | | |1 | |PSCBS |0.66.0 | | | | |PUMP |1.0.1 | | | | @@ -248,12 +248,13 @@ |refineR |1.5.1 | | | | |[regmedint](problems.md#regmedint)|1.0.0 | | |1 | |remiod |1.0.2 | | | | -|[reproducible](problems.md#reproducible)|1.2.16 |1 | | | +|reproducible |1.2.16 | | | | |reval |3.1-0 | | | | |[rgee](problems.md#rgee) |1.1.5 | | |2 | |[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | |robust2sls |0.2.2 | | | | |RTransferEntropy |0.2.21 | | | | +|s3fs |0.1.2 | | | | |[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | |[scBubbletree](failures.md#scbubbletree)|1.0.0 |1 | | | |[scDiffCom](problems.md#scdiffcom)|0.1.0 |1 | |2 | @@ -298,7 +299,7 @@ |startR |2.2.1 | | | | |steps |1.3.0 | | | | |supercells |0.9.1 | | | | -|[synergyfinder](problems.md#synergyfinder)|3.6.2 | |1 |2 | +|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | |[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | |[tarchetypes](failures.md#tarchetypes)|0.7.4 |1 | | | |[targeted](problems.md#targeted)|0.3 | | |1 | @@ -309,8 +310,8 @@ |[text](problems.md#text) |0.9.99.2 | | |1 | |tglkmeans |0.3.5 | | | | |tidyqwi |0.1.2 | | | | -|TKCat |1.0.6 | | | | -|[TreeSearch](failures.md#treesearch)|1.2.0 |1 | | | +|TKCat |1.0.7 | | | | +|[TreeSearch](failures.md#treesearch)|1.3.0 |1 | | | |[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | |tsfeatures |1.1 | | | | |[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | @@ -320,8 +321,8 @@ |[vmeasur](failures.md#vmeasur)|0.1.4 |1 | | | |webdeveloper |1.0.5 | | | | |whitewater |0.1.2 | | | | -|wildmeta |0.3.0 | | | | +|wildmeta |0.3.1 | | | | |[wru](problems.md#wru) |1.0.1 | | |2 | |[XNAString](problems.md#xnastring)|1.6.0 | | |3 | -|yfR |1.0.6 | | | | +|yfR |1.1.0 | | | | diff --git a/revdep/cran.md b/revdep/cran.md index ea832cef..25adbd1b 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,6 +1,6 @@ ## revdepcheck results -We checked 279 reverse dependencies (260 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 280 reverse dependencies (261 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. * We saw 0 new problems * We failed to check 5 packages diff --git a/revdep/failures.md b/revdep/failures.md index aea9391e..c8ca2bc5 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -2,10 +2,10 @@
-* Version: 4.0.3 +* Version: 4.0.4 * GitHub: https://github.com/sipss/AlpsNMR * Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2023-02-10 +* Date/Publication: 2023-02-16 * Number of recursive dependencies: 169 Run `revdep_details(, "AlpsNMR")` for more info @@ -276,10 +276,10 @@ ERROR: lazy loading failed for package ‘ChromSCape’
-* Version: 1.30.5 +* Version: 1.30.6 * GitHub: https://github.com/prostarproteomics/Prostar * Source code: https://github.com/cran/Prostar -* Date/Publication: 2023-02-10 +* Date/Publication: 2023-02-17 * Number of recursive dependencies: 166 Run `revdep_details(, "Prostar")` for more info @@ -532,11 +532,11 @@ ERROR: lazy loading failed for package ‘tarchetypes’
-* Version: 1.2.0 +* Version: 1.3.0 * GitHub: https://github.com/ms609/TreeSearch * Source code: https://github.com/cran/TreeSearch -* Date/Publication: 2022-08-10 22:40:17 UTC -* Number of recursive dependencies: 117 +* Date/Publication: 2023-02-20 09:40:07 UTC +* Number of recursive dependencies: 122 Run `revdep_details(, "TreeSearch")` for more info @@ -561,7 +561,7 @@ Run `revdep_details(, "TreeSearch")` for more info ** libs gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o @@ -588,7 +588,7 @@ ERROR: lazy loading failed for package ‘TreeSearch’ ** libs gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o diff --git a/revdep/problems.md b/revdep/problems.md index f7a30019..6347603d 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -26,10 +26,10 @@ Run `revdep_details(, "AIPW")` for more info
-* Version: 4.0.3 +* Version: 4.0.4 * GitHub: https://github.com/sipss/AlpsNMR * Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2023-02-10 +* Date/Publication: 2023-02-16 * Number of recursive dependencies: 169 Run `revdep_details(, "AlpsNMR")` for more info @@ -944,6 +944,33 @@ Run `revdep_details(, "EpiNow2")` for more info
+## Newly fixed + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + --- re-building ‘case-studies.Rmd’ using rmarkdown + --- finished re-building ‘case-studies.Rmd’ + + --- re-building ‘estimate_infections.Rmd’ using rmarkdown + --- finished re-building ‘estimate_infections.Rmd’ + + --- re-building ‘estimate_secondary.Rmd’ using rmarkdown + --- finished re-building ‘estimate_secondary.Rmd’ + + ... + ConnectionTimeout + Error: processing vignette 'estimate_truncation.Rmd' failed with diagnostics: + pandoc document conversion failed with error 61 + --- failed re-building ‘estimate_truncation.Rmd’ + + SUMMARY: processing the following file failed: + ‘estimate_truncation.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + ## In both * checking installed package size ... NOTE @@ -1645,7 +1672,7 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 12039 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 253498 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 ERROR Running the tests in ‘tests/testthat.R’ failed. @@ -2558,10 +2585,10 @@ Run `revdep_details(, "promises")` for more info
-* Version: 1.30.5 +* Version: 1.30.6 * GitHub: https://github.com/prostarproteomics/Prostar * Source code: https://github.com/cran/Prostar -* Date/Publication: 2023-02-10 +* Date/Publication: 2023-02-17 * Number of recursive dependencies: 166 Run `revdep_details(, "Prostar")` for more info @@ -2740,47 +2767,6 @@ Run `revdep_details(, "regmedint")` for more info All declared Imports should be used. ``` -# reproducible - -
- -* Version: 1.2.16 -* GitHub: https://github.com/PredictiveEcology/reproducible -* Source code: https://github.com/cran/reproducible -* Date/Publication: 2022-12-22 09:50:02 UTC -* Number of recursive dependencies: 104 - -Run `revdep_details(, "reproducible")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 11278 Segmentation fault (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 - - ERROR - Running the tests in ‘tests/test-all.R’ failed. - Last 50 lines of output: - adding: scratch/henrik/RtmprFW55G/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) - adding: scratch/henrik/RtmprFW55G/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) - - *** caught segfault *** - address 0x8, cause 'memory not mapped' - ... - 36: doTryCatch(return(expr), name, parentenv, handler) - 37: tryCatchOne(expr, names, parentenv, handlers[[1L]]) - 38: tryCatchList(expr, classes, parentenv, handlers) - 39: tryCatch(code, testthat_abort_reporter = function(cnd) { cat(conditionMessage(cnd), "\n") NULL}) - 40: with_reporter(reporters$multi, lapply(test_paths, test_one_file, env = env, wrap = wrap)) - 41: test_files_serial(test_dir = test_dir, test_package = test_package, test_paths = test_paths, load_helpers = load_helpers, reporter = reporter, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package) - 42: test_files(test_dir = path, test_paths = test_paths, test_package = package, reporter = reporter, load_helpers = load_helpers, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package, parallel = parallel) - 43: test_dir("testthat", package = package, reporter = reporter, ..., load_package = "installed") - 44: test_check("reproducible") - An irrecoverable exception occurred. R is aborting now ... - ``` - # rgee
@@ -3621,10 +3607,10 @@ Run `revdep_details(, "stars")` for more info
-* Version: 3.6.2 +* Version: 3.6.3 * GitHub: NA * Source code: https://github.com/cran/synergyfinder -* Date/Publication: 2022-12-22 +* Date/Publication: 2023-02-13 * Number of recursive dependencies: 191 Run `revdep_details(, "synergyfinder")` for more info @@ -3826,11 +3812,11 @@ Run `revdep_details(, "text")` for more info
-* Version: 1.2.0 +* Version: 1.3.0 * GitHub: https://github.com/ms609/TreeSearch * Source code: https://github.com/cran/TreeSearch -* Date/Publication: 2022-08-10 22:40:17 UTC -* Number of recursive dependencies: 117 +* Date/Publication: 2023-02-20 09:40:07 UTC +* Number of recursive dependencies: 122 Run `revdep_details(, "TreeSearch")` for more info @@ -3855,7 +3841,7 @@ Run `revdep_details(, "TreeSearch")` for more info ** libs gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o @@ -3882,7 +3868,7 @@ ERROR: lazy loading failed for package ‘TreeSearch’ ** libs gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o From c75b7207fd3e646b7638c203bda96f6592530e3e Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 23 Feb 2023 14:20:59 +0100 Subject: [PATCH 59/88] troubleshoot future.tests errors on MS Windows [ci skip] --- DESCRIPTION | 2 +- R/expressions.R | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 2a4e6b1f..99d5bb8f 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9007 +Version: 1.31.0-9008 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/expressions.R b/R/expressions.R index b26200d4..f11399a4 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -114,7 +114,11 @@ makeExpression <- local({ } if (length(args) > 0) base::do.call(base::Sys.setenv, args = args) - base::rm(list = c("args", "names", "old_names", "NAMES", "envs", "common", "added", "removed")) + base::rm(list = c("args")) + base::rm(list = c("names", "old_names")) + base::rm(list = c("common", "added", "removed")) + base::rm(list = c("NAMES", "envs")) +# base::rm(list = c("args", "names", "old_names", "NAMES", "envs", "common", "added", "removed")) } else { base::do.call(base::Sys.setenv, args = base::as.list(...future.oldEnvVars)) } From df8ba862a6e7fddd2b55a594ff1dc30c5242e4df Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 23 Feb 2023 14:30:16 +0100 Subject: [PATCH 60/88] troubleshoot future.tests errors on MS Windows - take 2 [ci skip] --- R/expressions.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/expressions.R b/R/expressions.R index f11399a4..65554871 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -114,10 +114,10 @@ makeExpression <- local({ } if (length(args) > 0) base::do.call(base::Sys.setenv, args = args) - base::rm(list = c("args")) base::rm(list = c("names", "old_names")) base::rm(list = c("common", "added", "removed")) base::rm(list = c("NAMES", "envs")) + base::rm(list = c("args")) # base::rm(list = c("args", "names", "old_names", "NAMES", "envs", "common", "added", "removed")) } else { base::do.call(base::Sys.setenv, args = base::as.list(...future.oldEnvVars)) From 432013a21b87e01339f2ed79e49738eeb5d18a07 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 23 Feb 2023 18:02:26 +0100 Subject: [PATCH 61/88] troubleshoot future.tests errors on MS Windows - take 3 [ci skip] --- R/expressions.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/expressions.R b/R/expressions.R index 65554871..2a65311a 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -114,7 +114,7 @@ makeExpression <- local({ } if (length(args) > 0) base::do.call(base::Sys.setenv, args = args) - base::rm(list = c("names", "old_names")) + base::rm(list = c("names", "old_names"), envir = environment(), inherits = FALSE) base::rm(list = c("common", "added", "removed")) base::rm(list = c("NAMES", "envs")) base::rm(list = c("args")) From e9a6f0afe2ced6485424d04f1725f168a0467db6 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 23 Feb 2023 18:19:24 +0100 Subject: [PATCH 62/88] troubleshoot future.tests errors on MS Windows - take 4 [ci skip] --- R/expressions.R | 7 ++----- 1 file changed, 2 insertions(+), 5 deletions(-) diff --git a/R/expressions.R b/R/expressions.R index 2a65311a..04ed6c86 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -114,11 +114,8 @@ makeExpression <- local({ } if (length(args) > 0) base::do.call(base::Sys.setenv, args = args) - base::rm(list = c("names", "old_names"), envir = environment(), inherits = FALSE) - base::rm(list = c("common", "added", "removed")) - base::rm(list = c("NAMES", "envs")) - base::rm(list = c("args")) -# base::rm(list = c("args", "names", "old_names", "NAMES", "envs", "common", "added", "removed")) + args <- names <- old_names <- NAMES <- envs <- common <- added <- removed <- NULL +# base::rm(list = c("args", "names", "old_names", "common", "added", "removed", "NAMES", "envs")) } else { base::do.call(base::Sys.setenv, args = base::as.list(...future.oldEnvVars)) } From 0177aaec2b25772dd9e43af08959556414ef6959 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 23 Feb 2023 18:53:38 +0100 Subject: [PATCH 63/88] troubleshoot future.tests errors on MS Windows - take 5 [ci skip] --- R/expressions.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/expressions.R b/R/expressions.R index 04ed6c86..01c0a9f7 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -115,7 +115,7 @@ makeExpression <- local({ if (length(args) > 0) base::do.call(base::Sys.setenv, args = args) args <- names <- old_names <- NAMES <- envs <- common <- added <- removed <- NULL -# base::rm(list = c("args", "names", "old_names", "common", "added", "removed", "NAMES", "envs")) + base::rm(list = c("args", "names", "old_names", "common", "added", "removed", "NAMES", "envs")) } else { base::do.call(base::Sys.setenv, args = base::as.list(...future.oldEnvVars)) } From 4790a839fc71c299b25691c0c5783c4d18e9e4db Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 24 Feb 2023 00:39:06 +0100 Subject: [PATCH 64/88] Cannot use base::rm() because it produces 'promise already under evaluation: recursive default argument reference or earlier problems?' in one of the future.tests tests and only on MS Windows; weird. Assign NULL values instead --- R/expressions.R | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/R/expressions.R b/R/expressions.R index 01c0a9f7..3c1c631e 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -114,8 +114,9 @@ makeExpression <- local({ } if (length(args) > 0) base::do.call(base::Sys.setenv, args = args) - args <- names <- old_names <- NAMES <- envs <- common <- added <- removed <- NULL - base::rm(list = c("args", "names", "old_names", "common", "added", "removed", "NAMES", "envs")) + + ## Not needed anymore + args <- names <- old_names <- NAMES <- envs <- common <- added <- removed <- NULL } else { base::do.call(base::Sys.setenv, args = base::as.list(...future.oldEnvVars)) } From 0a90ef52a5afdeaf2fe198b43420afa86de11159 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 24 Feb 2023 10:26:06 +0100 Subject: [PATCH 65/88] DEPRECATION: Removed temporary allowance for the 'civis' package to use the 'local' argument has been removed --- DESCRIPTION | 2 +- R/Future-class.R | 24 ++---------------------- 2 files changed, 3 insertions(+), 23 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 99d5bb8f..1b63e09e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9008 +Version: 1.31.0-9009 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/Future-class.R b/R/Future-class.R index b7569626..ec2c104b 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -163,29 +163,9 @@ Future <- function(expr = NULL, envir = parent.frame(), substitute = TRUE, stdou .Defunct(msg = "Future field 'value' is defunct and must not be set", package = .packageName) } - ## 'local' is now defunct + ## 'local' is defunct if ("local" %in% args_names) { - dfcn <- .Defunct - msg <- "Argument 'local' is defunct as of future 1.31.0 (2023-01-31)" - - ## SPECIAL CASE: Temporarily allow the 'civis' package to keep using - ## 'local' for a tad longer, although it has zero effect since a - ## long time (https://github.com/civisanalytics/civis-r/issues/244) - ## Only allow for this is local = TRUE and interactive mode (to - ## prevent it from breaking 'R CMD check') - ## /HB 2023-02-09 - if (isTRUE(args$local) && - Sys.getenv("R_FUTURE_CHECK_IGNORE_CIVIS", "true") == "true") { - for (call in sys.calls()) { - if ("CivisFuture" %in% as.character(call[[1]])) { - msg <- sprintf("%s. In this case it was because civis::CivisFuture() was used. Please contact the maintainers of the 'civis' package about this problem.", msg) - if (!interactive()) dfcn <- .Deprecated - break - } - } - } - - dfcn(msg = msg, package = .packageName) + .Defunct(msg = "Argument 'local' is defunct as of future 1.31.0 (2023-01-31)", package = .packageName) } core <- new.env(parent = emptyenv()) From 863cb39ce58f58b56b4510a2001ca1bb0d3fffc0 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 24 Feb 2023 10:30:43 +0100 Subject: [PATCH 66/88] GHA: modernize --- .github/workflows/R-CMD-check.yaml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index 9835a963..f4aab0de 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -50,6 +50,7 @@ jobs: _R_CHECK_MATRIX_DATA_: true _R_CHECK_SUGGESTS_ONLY_: true _R_CHECK_THINGS_IN_TEMP_DIR_: true + RCMDCHECK_ERROR_ON=note ## Specific to futures R_FUTURE_RNG_ONMISUSE: error R_FUTURE_GLOBALS_KEEPWHERE: ${{ matrix.config.globals_keepWhere }} @@ -100,9 +101,9 @@ jobs: R_FUTURE_FORK_MULTITHREADING_ENABLE: ${{ matrix.config.fork_multithreading_enable }} R_FUTURE_PSOCK_RELAY_IMMEDIATE: ${{ matrix.config.psock_relay_immediate }} run: | + if (nzchar(Sys.getenv("R_FUTURE_PLAN")) || getRversion() < "3.5.0") Sys.setenv(RCMDCHECK_ERROR_ON = "error") rcmdcheck::rcmdcheck( - args = c("--no-manual", "--as-cran"), - error_on = if (nzchar(Sys.getenv("R_FUTURE_PLAN"))) "error" else "note", + args = c("--no-manual", "--as-cran", if (getRversion() < "3.5.0") c("--no-vignettes", "--no-build-vignettes", "--ignore-vignettes")), check_dir = "check" ) shell: Rscript {0} @@ -112,7 +113,6 @@ jobs: run: | rcmdcheck::rcmdcheck( args = c("--no-manual", "--as-cran", if (.Platform$OS.type == "windows" && getRversion() >= "4.2.0") "--no-multiarch"), - error_on = "note", check_dir = "check" ) shell: Rscript {0} From 3004830d10f303830dc57851ed3dd88d83679a4a Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 24 Feb 2023 10:39:15 +0100 Subject: [PATCH 67/88] GHA: fix --- .github/workflows/R-CMD-check.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index f4aab0de..8559cbdd 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -50,7 +50,7 @@ jobs: _R_CHECK_MATRIX_DATA_: true _R_CHECK_SUGGESTS_ONLY_: true _R_CHECK_THINGS_IN_TEMP_DIR_: true - RCMDCHECK_ERROR_ON=note + RCMDCHECK_ERROR_ON: note ## Specific to futures R_FUTURE_RNG_ONMISUSE: error R_FUTURE_GLOBALS_KEEPWHERE: ${{ matrix.config.globals_keepWhere }} From edd26f11f747e39b872038323ac60692b1db98cb Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sat, 25 Feb 2023 02:17:20 -0800 Subject: [PATCH 68/88] REVDEP: 280 revdep packages [ci skip] --- revdep/README.md | 585 ++++++++-------- revdep/cran.md | 15 +- revdep/failures.md | 673 +----------------- revdep/problems.md | 1650 ++++++++++---------------------------------- 4 files changed, 651 insertions(+), 2272 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index c1397fdd..70ac5b47 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,14 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-20 | +|date |2023-02-25 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9007 |* | +|future |1.31.0 |1.31.0-9009 |* | |codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -26,303 +26,294 @@ # Revdeps -## Failed to check (10) +## New problems (1) -|package |version |error |warning |note | -|:------------|:-------|:-----|:-------|:----| -|[AlpsNMR](failures.md#alpsnmr)|4.0.4 |1 | | | -|[bayesian](failures.md#bayesian)|0.0.9 |1 | | | -|[brms](failures.md#brms)|2.18.0 |1 | |1 | -|[ChromSCape](failures.md#chromscape)|1.8.0 |1 | |2 | -|[Prostar](failures.md#prostar)|1.30.6 |1 | | | -|[scBubbletree](failures.md#scbubbletree)|1.0.0 |1 | | | -|[signeR](failures.md#signer)|2.0.2 |1 | | | -|[tarchetypes](failures.md#tarchetypes)|0.7.4 |1 | | | -|[TreeSearch](failures.md#treesearch)|1.3.0 |1 | | | -|[vmeasur](failures.md#vmeasur)|0.1.4 |1 | | | +|package |version |error |warning |note | +|:-------|:-------|:------|:-------|:----| +|[civis](problems.md#civis)|3.1.0 |__+1__ | | | ## All (280) -|package |version |error |warning |note | -|:------------------------|:---------|:-----|:-------|:----| -|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | -|alookr |0.3.7 | | | | -|alphaci |1.0.0 | | | | -|[AlpsNMR](failures.md#alpsnmr)|4.0.4 |1 | | | -|arkdb |0.0.16 | | | | -|aroma.affymetrix |3.2.1 | | | | -|aroma.cn |1.7.0 | | | | -|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | -|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | -|[bamm](problems.md#bamm) |0.4.3 |1 | | | -|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | -|BatchGetSymbols |2.6.4 | | | | -|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | -|[bayesian](failures.md#bayesian)|0.0.9 |1 | | | -|bayesmove |0.2.1 | | | | -|bcmaps |1.1.0 | | | | -|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | -|bhmbasket |0.9.5 | | | | -|[bigDM](problems.md#bigdm)|0.5.0 | | |2 | -|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | -|bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan)|0.4-6 | | |3 | -|bolasso |0.2.0 | | | | -|[brms](failures.md#brms) |2.18.0 |1 | |1 | -|brpop |0.1.5 | | | | -|[canaper](problems.md#canaper)|1.0.0 |1 | | | -|[ceRNAnetsim](problems.md#cernanetsim)|1.10.0 |1 | | | -|cft |1.0.0 | | | | -|[ChromSCape](failures.md#chromscape)|1.8.0 |1 | |2 | -|[civis](problems.md#civis)|3.0.0 | | |1 | -|Clustering |1.7.7 | | | | -|codalm |0.1.2 | | | | -|[codebook](problems.md#codebook)|0.9.2 | | |3 | -|conformalInference.fd |1.1.1 | | | | -|conformalInference.multi |1.1.1 | | | | -|crossmap |0.4.0 | | | | -|CSCNet |0.1.2 | | | | -|[cSEM](problems.md#csem) |0.5.0 | | |1 | -|[CSGo](problems.md#csgo) |0.6.7 | | |1 | -|cvCovEst |1.2.0 | | | | -|dagHMM |0.1.0 | | | | -|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | -|[delayed](problems.md#delayed)|0.4.0 |1 | | | -|dhReg |0.1.1 | | | | -|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | -|disk.frame |0.8.0 | | | | -|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | -|doFuture |0.12.2 | | | | -|DQAstats |0.3.2 | | | | -|[dragon](problems.md#dragon)|1.2.1 |1 | | | -|[drake](problems.md#drake)|7.13.4 |1 | | | -|drimmR |1.0.1 | | | | -|drtmle |1.1.2 | | | | -|dsos |0.1.2 | | | | -|DT |0.27 | | | | -|easyalluvial |0.3.1 | | | | -|ecic |0.0.2 | | | | -|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | -|elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.17 | |1 | | -|[EpiNow2](problems.md#epinow2)|1.3.4 |-1 | |2 | -|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | -|epwshiftr |0.1.3 | | | | -|ezcox |1.0.2 | | | | -|fabletools |0.3.2 | | | | -|FAMoS |0.3.0 | | | | -|fastRhockey |0.4.0 | | | | -|[fect](problems.md#fect) |1.0.0 | | |2 | -|fiery |1.1.4 | | | | -|finbif |0.7.2 | | | | -|fitlandr |0.1.0 | | | | -|[flowGraph](problems.md#flowgraph)|1.6.0 |1 | | | -|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | -|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | -|fst4pg |1.0.0 | | | | -|fundiversity |1.1.1 | | | | -|funGp |0.3.1 | | | | -|furrr |0.3.1 | | | | -|future.apply |1.10.0 | | | | -|future.batchtools |0.11.0 | | | | -|future.callr |0.8.1 | | | | -|future.tests |0.5.0 | | | | -|fxTWAPLS |0.1.2 | | | | -|[genBaRcode](problems.md#genbarcode)|1.2.5 |1 | | | -|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | -|GetBCBData |0.7.0 | | | | -|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | -|googlePubsubR |0.0.3 | | | | -|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | -|[greed](problems.md#greed)|0.6.1 | | |3 | -|greta |0.4.3 | | | | -|gstat |2.1-0 | | | | -|GSVA |1.46.0 | | | | -|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | -|gtfs2emis |0.1.0 | | | | -|gtfs2gps |2.1-0 | | | | -|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | -|hacksig |0.1.2 | | | | -|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | -|haldensify |0.2.3 | | | | -|hoopR |1.8.0 | | | | -|[hwep](problems.md#hwep) |2.0.0 | | |2 | -|idmodelr |0.4.0 | | | | -|imagefluency |0.2.4 | | | | -|iml |0.11.1 | | | | -|incubate |1.2.0 | | | | -|[infercnv](problems.md#infercnv)|1.14.0 |1 | | | -|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | -|[InPAS](problems.md#inpas)|2.6.0 | | |1 | -|[interflex](problems.md#interflex)|1.2.6 | | |1 | -|ipc |0.1.4 | | | | -|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | -|isopam |1.1.0 | | | | -|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | -|JointAI |1.0.4 | | | | -|jstor |0.3.10 | | | | -|JuliaConnectoR |1.1.1 | | | | -|kernelboot |0.1.9 | | | | -|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | -|latentcor |2.0.1 | | | | -|[lava](problems.md#lava) |1.7.1 | | |1 | -|ldaPrototype |0.3.1 | | | | -|ldsr |0.0.2 | | | | -|lemna |1.0.0 | | | | -|LexFindR |1.0.2 | | | | -|lgr |0.4.4 | | | | -|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | -|[lightr](problems.md#lightr)|1.7.0 | | |2 | -|lmtp |1.3.1 | | | | -|LWFBrook90R |0.5.2 | | | | -|[MAI](problems.md#mai) |1.4.0 | | |1 | -|MAMS |2.0.0 | | | | -|marginaleffects |0.9.0 | | | | -|mcmcensemble |3.0.0 | | | | -|mcp |0.3.2 | | | | -|merTools |0.5.2 | | | | -|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | -|[mice](problems.md#mice) |3.15.0 | |1 | | -|[microservices](problems.md#microservices)|0.2.0 |1 | | | -|microSTASIS |0.1.0 | | | | -|[migraph](problems.md#migraph)|0.13.2 |1 | | | -|mikropml |1.5.0 | | | | -|[MineICA](problems.md#mineica)|1.38.0 |1 | | | -|[missSBM](problems.md#misssbm)|1.0.3 |1 | | | -|[mistyR](problems.md#mistyr)|1.6.0 |3 | |1 | -|mlr3 |0.14.1 | | | | -|mlr3db |0.5.0 | | | | -|[mlr3pipelines](problems.md#mlr3pipelines)|0.4.2 |2 | |1 | -|mlr3spatial |0.3.1 | | | | -|modelsummary |1.3.0 | | | | -|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | -|MOSS |0.2.2 | | | | -|mrgsim.parallel |0.2.1 | | | | -|[mslp](problems.md#mslp) |1.0.1 |1 | | | -|multiverse |0.6.1 | | | | -|[netShiny](problems.md#netshiny)|1.0 |1 | | | -|NetSimR |0.1.2 | | | | -|nfl4th |1.0.2 | | | | -|nflfastR |4.5.1 | | | | -|nflseedR |1.2.0 | | | | -|[nncc](problems.md#nncc) |1.0.0 |1 | | | -|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | -|onemapsgapi |1.1.0 | | | | -|[OOS](problems.md#oos) |1.0.0 | | |1 | -|origami |1.0.7 | | | | -|paramsim |0.1.0 | | | | -|[partR2](problems.md#partr2)|0.9.1 | | |1 | -|[pavo](problems.md#pavo) |2.8.0 | |1 | | -|pbapply |1.7-0 | | | | -|PCRedux |1.1-2 | | | | -|PeakSegDisk |2022.2.1 | | | | -|penaltyLearning |2020.5.13 | | | | -|[pGRN](problems.md#pgrn) |0.3.5 |1 | | | -|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | -|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | -|PINstimation |0.1.1 | | | | -|[PLNmodels](problems.md#plnmodels)|1.0.1 |1 | | | -|plumber |1.2.1 | | | | -|polle |1.2 | | | | -|POMADE |0.1.0 | | | | -|[portvine](problems.md#portvine)|1.0.2 | | |1 | -|powRICLPM |0.1.1 | | | | -|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | -|[prewas](problems.md#prewas)|1.1.1 |2 | |1 | -|progressr |0.13.0 | | | | -|[projpred](problems.md#projpred)|2.4.0 |1 | |1 | -|[promises](problems.md#promises)|1.2.0.1 | | |1 | -|[Prostar](failures.md#prostar)|1.30.6 |1 | | | -|[protti](problems.md#protti)|0.6.0 | | |1 | -|PSCBS |0.66.0 | | | | -|PUMP |1.0.1 | | | | -|qape |2.0 | | | | -|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | -|qgcomp |2.10.1 | | | | -|qgcompint |0.7.0 | | | | -|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | -|[rangeMapper](problems.md#rangemapper)|2.0.3 | | |1 | -|rBiasCorrection |0.3.4 | | | | -|receptiviti |0.1.3 | | | | -|refineR |1.5.1 | | | | -|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | -|remiod |1.0.2 | | | | -|reproducible |1.2.16 | | | | -|reval |3.1-0 | | | | -|[rgee](problems.md#rgee) |1.1.5 | | |2 | -|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | -|robust2sls |0.2.2 | | | | -|RTransferEntropy |0.2.21 | | | | -|s3fs |0.1.2 | | | | -|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | -|[scBubbletree](failures.md#scbubbletree)|1.0.0 |1 | | | -|[scDiffCom](problems.md#scdiffcom)|0.1.0 |1 | |2 | -|SCtools |0.3.2.1 | | | | -|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | -|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | -|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | -|seer |1.1.8 | | | | -|semtree |0.9.18 | | | | -|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | -|[Seurat](problems.md#seurat)|4.3.0 |1 | | | -|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | -|[shiny](problems.md#shiny)|1.7.4 | | |1 | -|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | -|sigminer |2.1.9 | | | | -|Signac |1.9.0 | | | | -|[signeR](failures.md#signer)|2.0.2 |1 | | | -|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | -|simfinapi |0.2.0 | | | | -|simglm |0.8.9 | | | | -|simhelpers |0.1.2 | | | | -|sims |0.0.3 | | | | -|skewlmm |1.0.0 | | | | -|[skpr](problems.md#skpr) |1.1.6 | | |1 | -|smoots |1.1.3 | | | | -|sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude)|1.1.3 |1 | | | -|sovereign |1.2.1 | | | | -|[spaMM](problems.md#spamm)|4.1.20 | | |2 | -|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | -|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | -|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | -|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | -|[specr](problems.md#specr)|1.0.0 |1 | | | -|sperrorest |3.0.5 | | | | -|spFSR |2.0.3 | | | | -|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork)|0.4.3.6 |1 | | | -|[squat](problems.md#squat)|0.1.0 | | |1 | -|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | -|[stars](problems.md#stars)|0.6-0 | | |2 | -|startR |2.2.1 | | | | -|steps |1.3.0 | | | | -|supercells |0.9.1 | | | | -|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | -|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | -|[tarchetypes](failures.md#tarchetypes)|0.7.4 |1 | | | -|[targeted](problems.md#targeted)|0.3 | | |1 | -|[targets](problems.md#targets)|0.14.2 |1 | | | -|tcplfit2 |0.1.3 | | | | -|tealeaves |1.0.6 | | | | -|templr |0.2-0 | | | | -|[text](problems.md#text) |0.9.99.2 | | |1 | -|tglkmeans |0.3.5 | | | | -|tidyqwi |0.1.2 | | | | -|TKCat |1.0.7 | | | | -|[TreeSearch](failures.md#treesearch)|1.3.0 |1 | | | -|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | -|tsfeatures |1.1 | | | | -|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | -|[txshift](problems.md#txshift)|0.3.8 | | |1 | -|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.9 | | |1 | -|[updog](problems.md#updog)|2.1.3 | | |1 | -|[vmeasur](failures.md#vmeasur)|0.1.4 |1 | | | -|webdeveloper |1.0.5 | | | | -|whitewater |0.1.2 | | | | -|wildmeta |0.3.1 | | | | -|[wru](problems.md#wru) |1.0.1 | | |2 | -|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | -|yfR |1.1.0 | | | | +|package |version |error |warning |note | +|:------------------------|:---------|:------|:-------|:----| +|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | +|alookr |0.3.7 | | | | +|alphaci |1.0.0 | | | | +|AlpsNMR |4.0.4 | | | | +|arkdb |0.0.16 | | | | +|aroma.affymetrix |3.2.1 | | | | +|aroma.cn |1.7.0 | | | | +|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | +|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | +|bamm |0.4.3 | | | | +|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | +|BatchGetSymbols |2.6.4 | | | | +|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | +|bayesian |0.0.9 | | | | +|bayesmove |0.2.1 | | | | +|bcmaps |1.1.0 | | | | +|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | +|bhmbasket |0.9.5 | | | | +|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | +|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | +|bkmrhat |1.1.3 | | | | +|[blavaan](problems.md#blavaan)|0.4-6 | | |3 | +|bolasso |0.2.0 | | | | +|[brms](problems.md#brms) |2.18.0 | | |2 | +|brpop |0.1.5 | | | | +|canaper |1.0.0 | | | | +|ceRNAnetsim |1.10.0 | | | | +|cft |1.0.0 | | | | +|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | +|[civis](problems.md#civis)|3.1.0 |__+1__ | | | +|Clustering |1.7.7 | | | | +|codalm |0.1.2 | | | | +|[codebook](problems.md#codebook)|0.9.2 | | |3 | +|conformalInference.fd |1.1.1 | | | | +|conformalInference.multi |1.1.1 | | | | +|crossmap |0.4.0 | | | | +|CSCNet |0.1.2 | | | | +|[cSEM](problems.md#csem) |0.5.0 | | |1 | +|[CSGo](problems.md#csgo) |0.6.7 | | |1 | +|cvCovEst |1.2.0 | | | | +|dagHMM |0.1.0 | | | | +|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | +|delayed |0.4.0 | | | | +|dhReg |0.1.1 | | | | +|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | +|disk.frame |0.8.0 | | | | +|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | +|doFuture |0.12.2 | | | | +|DQAstats |0.3.2 | | | | +|[dragon](problems.md#dragon)|1.2.1 | | |1 | +|drake |7.13.4 | | | | +|drimmR |1.0.1 | | | | +|drtmle |1.1.2 | | | | +|dsos |0.1.2 | | | | +|DT |0.27 | | | | +|easyalluvial |0.3.1 | | | | +|ecic |0.0.3 | | | | +|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | +|elevatr |0.4.2 | | | | +|[envi](problems.md#envi) |0.1.17 | |1 | | +|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | +|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | +|epwshiftr |0.1.3 | | | | +|ezcox |1.0.2 | | | | +|fabletools |0.3.2 | | | | +|FAMoS |0.3.0 | | | | +|fastRhockey |0.4.0 | | | | +|[fect](problems.md#fect) |1.0.0 | | |2 | +|fiery |1.1.4 | | | | +|finbif |0.7.2 | | | | +|fitlandr |0.1.0 | | | | +|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | +|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | +|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | +|fst4pg |1.0.0 | | | | +|fundiversity |1.1.1 | | | | +|funGp |0.3.1 | | | | +|furrr |0.3.1 | | | | +|future.apply |1.10.0 | | | | +|future.batchtools |0.12.0 | | | | +|future.callr |0.8.1 | | | | +|future.tests |0.5.0 | | | | +|fxTWAPLS |0.1.2 | | | | +|genBaRcode |1.2.5 | | | | +|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | +|GetBCBData |0.7.0 | | | | +|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | +|googlePubsubR |0.0.3 | | | | +|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | +|[greed](problems.md#greed)|0.6.1 | | |2 | +|greta |0.4.3 | | | | +|gstat |2.1-0 | | | | +|GSVA |1.46.0 | | | | +|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | +|gtfs2emis |0.1.0 | | | | +|gtfs2gps |2.1-0 | | | | +|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | +|hacksig |0.1.2 | | | | +|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | +|haldensify |0.2.3 | | | | +|hoopR |1.8.0 | | | | +|[hwep](problems.md#hwep) |2.0.0 | | |2 | +|idmodelr |0.4.0 | | | | +|imagefluency |0.2.4 | | | | +|iml |0.11.1 | | | | +|incubate |1.2.0 | | | | +|[infercnv](problems.md#infercnv)|1.14.0 | | |2 | +|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | +|[InPAS](problems.md#inpas)|2.6.0 | | |1 | +|[interflex](problems.md#interflex)|1.2.6 | | |1 | +|ipc |0.1.4 | | | | +|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | +|isopam |1.1.0 | | | | +|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | +|JointAI |1.0.4 | | | | +|jstor |0.3.10 | | | | +|JuliaConnectoR |1.1.1 | | | | +|kernelboot |0.1.9 | | | | +|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | +|latentcor |2.0.1 | | | | +|lava |1.7.2 | | | | +|ldaPrototype |0.3.1 | | | | +|ldsr |0.0.2 | | | | +|lemna |1.0.0 | | | | +|LexFindR |1.0.2 | | | | +|lgr |0.4.4 | | | | +|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | +|[lightr](problems.md#lightr)|1.7.0 | | |2 | +|lmtp |1.3.1 | | | | +|LWFBrook90R |0.5.2 | | | | +|[MAI](problems.md#mai) |1.4.0 | | |1 | +|MAMS |2.0.0 | | | | +|marginaleffects |0.10.0 | | | | +|mcmcensemble |3.0.0 | | | | +|mcp |0.3.2 | | | | +|merTools |0.5.2 | | | | +|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | +|[mice](problems.md#mice) |3.15.0 | |1 | | +|[microservices](problems.md#microservices)|0.2.0 |1 | | | +|microSTASIS |0.1.0 | | | | +|migraph |0.13.2 | | | | +|mikropml |1.5.0 | | | | +|[MineICA](problems.md#mineica)|1.38.0 | |3 |4 | +|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | +|[mistyR](problems.md#mistyr)|1.6.1 | | |1 | +|mlr3 |0.14.1 | | | | +|mlr3db |0.5.0 | | | | +|mlr3pipelines |0.4.2 | | | | +|mlr3spatial |0.3.1 | | | | +|modelsummary |1.3.0 | | | | +|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | +|MOSS |0.2.2 | | | | +|mrgsim.parallel |0.2.1 | | | | +|[mslp](problems.md#mslp) |1.0.1 |1 | | | +|multiverse |0.6.1 | | | | +|netShiny |1.0 | | | | +|NetSimR |0.1.2 | | | | +|nfl4th |1.0.2 | | | | +|nflfastR |4.5.1 | | | | +|nflseedR |1.2.0 | | | | +|nncc |1.0.0 | | | | +|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | +|onemapsgapi |1.1.0 | | | | +|[OOS](problems.md#oos) |1.0.0 | | |1 | +|origami |1.0.7 | | | | +|paramsim |0.1.0 | | | | +|[partR2](problems.md#partr2)|0.9.1 | | |1 | +|[pavo](problems.md#pavo) |2.8.0 | |1 | | +|pbapply |1.7-0 | | | | +|PCRedux |1.1-2 | | | | +|PeakSegDisk |2022.2.1 | | | | +|penaltyLearning |2020.5.13 | | | | +|pGRN |0.3.5 | | | | +|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | +|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | +|PINstimation |0.1.1 | | | | +|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | +|plumber |1.2.1 | | | | +|polle |1.2 | | | | +|POMADE |0.1.0 | | | | +|[portvine](problems.md#portvine)|1.0.2 | | |1 | +|powRICLPM |0.1.1 | | | | +|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | +|[prewas](problems.md#prewas)|1.1.1 | | |1 | +|progressr |0.13.0 | | | | +|[projpred](problems.md#projpred)|2.4.0 | | |1 | +|[promises](problems.md#promises)|1.2.0.1 | | |1 | +|Prostar |1.30.7 | | | | +|protti |0.6.0 | | | | +|PSCBS |0.66.0 | | | | +|PUMP |1.0.1 | | | | +|qape |2.0 | | | | +|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | +|qgcomp |2.10.1 | | | | +|qgcompint |0.7.0 | | | | +|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | +|rangeMapper |2.0.3 | | | | +|rBiasCorrection |0.3.4 | | | | +|receptiviti |0.1.3 | | | | +|refineR |1.5.1 | | | | +|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | +|remiod |1.0.2 | | | | +|reproducible |1.2.16 |-1 | | | +|reval |3.1-0 | | | | +|[rgee](problems.md#rgee) |1.1.5 | | |2 | +|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | +|robust2sls |0.2.2 | | | | +|RTransferEntropy |0.2.21 | | | | +|s3fs |0.1.2 | | | | +|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | +|scBubbletree |1.0.0 | | | | +|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | +|SCtools |0.3.2.1 | | | | +|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | +|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | +|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | +|seer |1.1.8 | | | | +|semtree |0.9.18 | | | | +|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[Seurat](problems.md#seurat)|4.3.0 | | |2 | +|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | +|[shiny](problems.md#shiny)|1.7.4 | | |1 | +|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | +|sigminer |2.1.9 | | | | +|Signac |1.9.0 | | | | +|[signeR](problems.md#signer)|2.0.2 | | |3 | +|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | +|simfinapi |0.2.0 | | | | +|simglm |0.8.9 | | | | +|simhelpers |0.1.2 | | | | +|sims |0.0.3 | | | | +|skewlmm |1.0.0 | | | | +|[skpr](problems.md#skpr) |1.1.6 | | |1 | +|smoots |1.1.3 | | | | +|sNPLS |1.0.27 | | | | +|[solitude](problems.md#solitude)|1.1.3 | | |1 | +|sovereign |1.2.1 | | | | +|[spaMM](problems.md#spamm)|4.1.20 | | |2 | +|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | +|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | +|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | +|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | +|specr |1.0.0 | | | | +|sperrorest |3.0.5 | | | | +|spFSR |2.0.3 | | | | +|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | +|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | +|[squat](problems.md#squat)|0.1.0 | | |1 | +|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | +|[stars](problems.md#stars)|0.6-0 | | |2 | +|startR |2.2.1 | | | | +|steps |1.3.0 | | | | +|supercells |0.9.1 | | | | +|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | +|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | +|tarchetypes |0.7.4 | | | | +|[targeted](problems.md#targeted)|0.3 | | |1 | +|targets |0.14.2 | | | | +|tcplfit2 |0.1.3 | | | | +|tealeaves |1.0.6 | | | | +|templr |0.2-0 | | | | +|[text](problems.md#text) |0.9.99.2 | | |1 | +|tglkmeans |0.3.5 | | | | +|tidyqwi |0.1.2 | | | | +|TKCat |1.0.7 | | | | +|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | +|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | +|tsfeatures |1.1 | | | | +|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | +|[txshift](problems.md#txshift)|0.3.8 | | |1 | +|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.9 | | |1 | +|[updog](problems.md#updog)|2.1.3 | | |1 | +|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | +|webdeveloper |1.0.5 | | | | +|whitewater |0.1.2 | | | | +|wildmeta |0.3.1 | | | | +|[wru](problems.md#wru) |1.0.1 | | |2 | +|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | +|yfR |1.1.0 | | | | diff --git a/revdep/cran.md b/revdep/cran.md index 25adbd1b..d32ba8d3 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,15 +2,14 @@ We checked 280 reverse dependencies (261 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 0 new problems - * We failed to check 5 packages + * We saw 1 new problems + * We failed to check 0 packages Issues with CRAN packages are summarised below. -### Failed to check +### New problems +(This reports the first line of each new failure) + +* civis + checking package dependencies ... ERROR -* bayesian (NA) -* brms (NA) -* tarchetypes (NA) -* TreeSearch (NA) -* vmeasur (NA) diff --git a/revdep/failures.md b/revdep/failures.md index c8ca2bc5..9a207363 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1,672 +1 @@ -# AlpsNMR - -
- -* Version: 4.0.4 -* GitHub: https://github.com/sipss/AlpsNMR -* Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2023-02-16 -* Number of recursive dependencies: 169 - -Run `revdep_details(, "AlpsNMR")` for more info - -
- -## In both - -* checking whether package ‘AlpsNMR’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘AlpsNMR’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘AlpsNMR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/AlpsNMR’ - - -``` -### CRAN - -``` -* installing *source* package ‘AlpsNMR’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘AlpsNMR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/old/AlpsNMR.Rcheck/AlpsNMR’ - - -``` -# bayesian - -
- -* Version: 0.0.9 -* GitHub: https://github.com/hsbadr/bayesian -* Source code: https://github.com/cran/bayesian -* Date/Publication: 2022-06-16 23:00:02 UTC -* Number of recursive dependencies: 186 - -Run `revdep_details(, "bayesian")` for more info - -
- -## In both - -* checking whether package ‘bayesian’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘bayesian’ ... -** package ‘bayesian’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘igraph’ -Execution halted -ERROR: lazy loading failed for package ‘bayesian’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/bayesian’ - - -``` -### CRAN - -``` -* installing *source* package ‘bayesian’ ... -** package ‘bayesian’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘igraph’ -Execution halted -ERROR: lazy loading failed for package ‘bayesian’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/old/bayesian.Rcheck/bayesian’ - - -``` -# brms - -
- -* Version: 2.18.0 -* GitHub: https://github.com/paul-buerkner/brms -* Source code: https://github.com/cran/brms -* Date/Publication: 2022-09-19 13:56:19 UTC -* Number of recursive dependencies: 181 - -Run `revdep_details(, "brms")` for more info - -
- -## In both - -* checking whether package ‘brms’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/00install.out’ for details. - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘cmdstanr’ - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘brms’ ... -** package ‘brms’ successfully unpacked and MD5 sums checked -** using staged installation -** R -Warning: namespace ‘brms’ is not available and has been replaced -by .GlobalEnv when processing object ‘brmsfit_example1’ -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘brms’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/brms’ - - -``` -### CRAN - -``` -* installing *source* package ‘brms’ ... -** package ‘brms’ successfully unpacked and MD5 sums checked -** using staged installation -** R -Warning: namespace ‘brms’ is not available and has been replaced -by .GlobalEnv when processing object ‘brmsfit_example1’ -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘brms’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/old/brms.Rcheck/brms’ - - -``` -# ChromSCape - -
- -* Version: 1.8.0 -* GitHub: https://github.com/vallotlab/ChromSCape -* Source code: https://github.com/cran/ChromSCape -* Date/Publication: 2022-11-01 -* Number of recursive dependencies: 227 - -Run `revdep_details(, "ChromSCape")` for more info - -
- -## In both - -* checking whether package ‘ChromSCape’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00install.out’ for details. - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ - ``` - -* checking for hidden files and directories ... NOTE - ``` - Found the following hidden files and directories: - .BBSoptions - These were most likely included in error. See section ‘Package - structure’ in the ‘Writing R Extensions’ manual. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘ChromSCape’ ... -** using staged installation -** libs -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o -g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘ChromSCape’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/ChromSCape’ - - -``` -### CRAN - -``` -* installing *source* package ‘ChromSCape’ ... -** using staged installation -** libs -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o -g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘ChromSCape’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/ChromSCape’ - - -``` -# Prostar - -
- -* Version: 1.30.6 -* GitHub: https://github.com/prostarproteomics/Prostar -* Source code: https://github.com/cran/Prostar -* Date/Publication: 2023-02-17 -* Number of recursive dependencies: 166 - -Run `revdep_details(, "Prostar")` for more info - -
- -## In both - -* checking whether package ‘Prostar’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘Prostar’ ... -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘Prostar’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/Prostar’ - - -``` -### CRAN - -``` -* installing *source* package ‘Prostar’ ... -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘Prostar’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/old/Prostar.Rcheck/Prostar’ - - -``` -# scBubbletree - -
- -* Version: 1.0.0 -* GitHub: https://github.com/snaketron/scBubbletree -* Source code: https://github.com/cran/scBubbletree -* Date/Publication: 2022-11-01 -* Number of recursive dependencies: 178 - -Run `revdep_details(, "scBubbletree")` for more info - -
- -## In both - -* checking whether package ‘scBubbletree’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘scBubbletree’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘scBubbletree’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/scBubbletree’ - - -``` -### CRAN - -``` -* installing *source* package ‘scBubbletree’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘scBubbletree’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/old/scBubbletree.Rcheck/scBubbletree’ - - -``` -# signeR - -
- -* Version: 2.0.2 -* GitHub: https://github.com/rvalieris/signeR -* Source code: https://github.com/cran/signeR -* Date/Publication: 2023-01-19 -* Number of recursive dependencies: 242 - -Run `revdep_details(, "signeR")` for more info - -
- -## In both - -* checking whether package ‘signeR’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘signeR’ ... -** using staged installation -** libs -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o -g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs -** R -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘signeR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/signeR’ - - -``` -### CRAN - -``` -* installing *source* package ‘signeR’ ... -** using staged installation -** libs -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o -g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs -** R -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘signeR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/signeR’ - - -``` -# tarchetypes - -
- -* Version: 0.7.4 -* GitHub: https://github.com/ropensci/tarchetypes -* Source code: https://github.com/cran/tarchetypes -* Date/Publication: 2023-01-06 18:50:20 UTC -* Number of recursive dependencies: 78 - -Run `revdep_details(, "tarchetypes")` for more info - -
- -## In both - -* checking whether package ‘tarchetypes’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘tarchetypes’ ... -** package ‘tarchetypes’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘tarchetypes’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/tarchetypes’ - - -``` -### CRAN - -``` -* installing *source* package ‘tarchetypes’ ... -** package ‘tarchetypes’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘tarchetypes’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/old/tarchetypes.Rcheck/tarchetypes’ - - -``` -# TreeSearch - -
- -* Version: 1.3.0 -* GitHub: https://github.com/ms609/TreeSearch -* Source code: https://github.com/cran/TreeSearch -* Date/Publication: 2023-02-20 09:40:07 UTC -* Number of recursive dependencies: 122 - -Run `revdep_details(, "TreeSearch")` for more info - -
- -## In both - -* checking whether package ‘TreeSearch’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘TreeSearch’ ... -** package ‘TreeSearch’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘TreeSearch’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/TreeSearch’ - - -``` -### CRAN - -``` -* installing *source* package ‘TreeSearch’ ... -** package ‘TreeSearch’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘TreeSearch’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/old/TreeSearch.Rcheck/TreeSearch’ - - -``` -# vmeasur - -
- -* Version: 0.1.4 -* GitHub: NA -* Source code: https://github.com/cran/vmeasur -* Date/Publication: 2021-11-11 19:00:02 UTC -* Number of recursive dependencies: 117 - -Run `revdep_details(, "vmeasur")` for more info - -
- -## In both - -* checking whether package ‘vmeasur’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘vmeasur’ ... -** package ‘vmeasur’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘vmeasur’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/vmeasur’ - - -``` -### CRAN - -``` -* installing *source* package ‘vmeasur’ ... -** package ‘vmeasur’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘vmeasur’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/old/vmeasur.Rcheck/vmeasur’ - - -``` +*Wow, no problems at all. :)* \ No newline at end of file diff --git a/revdep/problems.md b/revdep/problems.md index 6347603d..8d97d0ad 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -22,66 +22,6 @@ Run `revdep_details(, "AIPW")` for more info All declared Imports should be used. ``` -# AlpsNMR - -
- -* Version: 4.0.4 -* GitHub: https://github.com/sipss/AlpsNMR -* Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2023-02-16 -* Number of recursive dependencies: 169 - -Run `revdep_details(, "AlpsNMR")` for more info - -
- -## In both - -* checking whether package ‘AlpsNMR’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘AlpsNMR’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘AlpsNMR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/new/AlpsNMR.Rcheck/AlpsNMR’ - - -``` -### CRAN - -``` -* installing *source* package ‘AlpsNMR’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘AlpsNMR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/AlpsNMR/old/AlpsNMR.Rcheck/AlpsNMR’ - - -``` # aroma.core
@@ -122,33 +62,9 @@ Run `revdep_details(, "BAMBI")` for more info * checking installed package size ... NOTE ``` - installed size is 7.2Mb + installed size is 7.1Mb sub-directories of 1Mb or more: - libs 6.7Mb - ``` - -# bamm - -
- -* Version: 0.4.3 -* GitHub: https://github.com/luismurao/bamm -* Source code: https://github.com/cran/bamm -* Date/Publication: 2022-12-20 11:10:05 UTC -* Number of recursive dependencies: 109 - -Run `revdep_details(, "bamm")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + libs 6.6Mb ``` # baseballr @@ -159,7 +75,7 @@ Run `revdep_details(, "bamm")` for more info * GitHub: https://github.com/BillPetti/baseballr * Source code: https://github.com/cran/baseballr * Date/Publication: 2022-09-09 07:52:55 UTC -* Number of recursive dependencies: 118 +* Number of recursive dependencies: 119 Run `revdep_details(, "baseballr")` for more info @@ -218,64 +134,6 @@ Run `revdep_details(, "batchtools")` for more info Package unavailable to check Rd xrefs: ‘Rmpi’ ``` -# bayesian - -
- -* Version: 0.0.9 -* GitHub: https://github.com/hsbadr/bayesian -* Source code: https://github.com/cran/bayesian -* Date/Publication: 2022-06-16 23:00:02 UTC -* Number of recursive dependencies: 186 - -Run `revdep_details(, "bayesian")` for more info - -
- -## In both - -* checking whether package ‘bayesian’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘bayesian’ ... -** package ‘bayesian’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘igraph’ -Execution halted -ERROR: lazy loading failed for package ‘bayesian’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/new/bayesian.Rcheck/bayesian’ - - -``` -### CRAN - -``` -* installing *source* package ‘bayesian’ ... -** package ‘bayesian’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘igraph’ -Execution halted -ERROR: lazy loading failed for package ‘bayesian’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/bayesian/old/bayesian.Rcheck/bayesian’ - - -``` # BEKKs
@@ -294,9 +152,9 @@ Run `revdep_details(, "BEKKs")` for more info * checking installed package size ... NOTE ``` - installed size is 18.4Mb + installed size is 18.3Mb sub-directories of 1Mb or more: - libs 17.5Mb + libs 17.4Mb ``` * checking dependencies in R code ... NOTE @@ -309,10 +167,10 @@ Run `revdep_details(, "BEKKs")` for more info
-* Version: 0.5.0 +* Version: 0.5.1 * GitHub: https://github.com/spatialstatisticsupna/bigDM * Source code: https://github.com/cran/bigDM -* Date/Publication: 2022-10-28 11:47:44 UTC +* Date/Publication: 2023-02-22 09:00:06 UTC * Number of recursive dependencies: 125 Run `revdep_details(, "bigDM")` for more info @@ -416,126 +274,17 @@ Run `revdep_details(, "brms")` for more info ## In both -* checking whether package ‘brms’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/00install.out’ for details. - ``` - * checking package dependencies ... NOTE ``` Package suggested but not available for checking: ‘cmdstanr’ ``` -## Installation - -### Devel - -``` -* installing *source* package ‘brms’ ... -** package ‘brms’ successfully unpacked and MD5 sums checked -** using staged installation -** R -Warning: namespace ‘brms’ is not available and has been replaced -by .GlobalEnv when processing object ‘brmsfit_example1’ -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘brms’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/new/brms.Rcheck/brms’ - - -``` -### CRAN - -``` -* installing *source* package ‘brms’ ... -** package ‘brms’ successfully unpacked and MD5 sums checked -** using staged installation -** R -Warning: namespace ‘brms’ is not available and has been replaced -by .GlobalEnv when processing object ‘brmsfit_example1’ -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘brms’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/brms/old/brms.Rcheck/brms’ - - -``` -# canaper - -
- -* Version: 1.0.0 -* GitHub: https://github.com/ropensci/canaper -* Source code: https://github.com/cran/canaper -* Date/Publication: 2022-10-04 10:20:12 UTC -* Number of recursive dependencies: 167 - -Run `revdep_details(, "canaper")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - 4. └─base::loadNamespace(x) - 5. ├─base::namespaceImportFrom(...) - 6. │ └─base::asNamespace(ns) - 7. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 8. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) - 9. └─base (local) withOneRestart(expr, restarts[[1L]]) - ... - 5. ├─base::namespaceImportFrom(...) - 6. │ └─base::asNamespace(ns) - 7. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 8. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) - 9. └─base (local) withOneRestart(expr, restarts[[1L]]) - 10. └─base (local) doWithOneRestart(return(expr), restart) - - [ FAIL 9 | WARN 0 | SKIP 0 | PASS 99 ] - Error: Test failures - Execution halted - ``` - -# ceRNAnetsim - -
- -* Version: 1.10.0 -* GitHub: https://github.com/selcenari/ceRNAnetsim -* Source code: https://github.com/cran/ceRNAnetsim -* Date/Publication: 2022-11-01 -* Number of recursive dependencies: 99 - -Run `revdep_details(, "ceRNAnetsim")` for more info - -
- -## In both - -* checking package dependencies ... ERROR +* checking installed package size ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + installed size is 7.5Mb + sub-directories of 1Mb or more: + R 3.0Mb + doc 3.6Mb ``` # ChromSCape @@ -554,92 +303,75 @@ Run `revdep_details(, "ChromSCape")` for more info ## In both -* checking whether package ‘ChromSCape’ can be installed ... ERROR +* checking for hidden files and directories ... NOTE ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00install.out’ for details. + Found the following hidden files and directories: + .BBSoptions + These were most likely included in error. See section ‘Package + structure’ in the ‘Writing R Extensions’ manual. ``` -* checking package dependencies ... NOTE +* checking installed package size ... NOTE + ``` + installed size is 8.2Mb + sub-directories of 1Mb or more: + data 1.4Mb + doc 2.9Mb + www 2.0Mb + ``` + +* checking R code for possible problems ... NOTE ``` - Package suggested but not available for checking: ‘igraph’ + bams_to_matrix_indexes: no visible binding for global variable + ‘files_dir_list’ + enrich_TF_ChEA3_genes: no visible binding for global variable + ‘CheA3_TF_nTargets’ + filter_correlated_cell_scExp: no visible binding for global variable + ‘run_tsne’ + generate_analysis: no visible binding for global variable ‘k’ + generate_analysis: no visible binding for global variable + ‘clusterConsensus’ + get_most_variable_cyto: no visible binding for global variable + ... + plot_top_TF_scExp: no visible binding for global variable ‘TF’ + rebin_matrix: no visible binding for global variable ‘new_row’ + rebin_matrix: no visible binding for global variable ‘origin_value’ + subset_bam_call_peaks: no visible binding for global variable + ‘merged_bam’ + Undefined global functions or variables: + CheA3_TF_nTargets Component Fri_cyto Gain_or_Loss Gene TF V1 V2 + absolute_value cluster clusterConsensus cytoBand files_dir_list genes + group k merged_bam molecule ncells new_row orientation origin_value + percent_active run_tsne sample_id total_counts ``` -* checking for hidden files and directories ... NOTE +* checking Rd files ... NOTE ``` - Found the following hidden files and directories: - .BBSoptions - These were most likely included in error. See section ‘Package - structure’ in the ‘Writing R Extensions’ manual. + prepare_Rd: raw_counts_to_sparse_matrix.Rd:6-8: Dropping empty section \source ``` -## Installation - -### Devel - -``` -* installing *source* package ‘ChromSCape’ ... -** using staged installation -** libs -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o -g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘ChromSCape’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/new/ChromSCape.Rcheck/ChromSCape’ - - -``` -### CRAN - -``` -* installing *source* package ‘ChromSCape’ ... -** using staged installation -** libs -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/ChromSCape/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c as_dist.cpp -o as_dist.o -g++ -std=gnu++14 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o ChromSCape.so RcppExports.o as_dist.o -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/00LOCK-ChromSCape/00new/ChromSCape/libs -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘ChromSCape’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/ChromSCape/old/ChromSCape.Rcheck/ChromSCape’ - - -``` # civis
-* Version: 3.0.0 +* Version: 3.1.0 * GitHub: https://github.com/civisanalytics/civis-r * Source code: https://github.com/cran/civis -* Date/Publication: 2020-06-22 18:00:02 UTC +* Date/Publication: 2023-02-22 23:10:06 UTC * Number of recursive dependencies: 88 Run `revdep_details(, "civis")` for more info
-## In both +## Newly broken -* checking LazyData ... NOTE +* checking package dependencies ... ERROR ``` - 'LazyData' is specified without a 'data' directory + Package required and available but unsuitable version: ‘future’ + + See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ + manual. ``` # codebook @@ -741,30 +473,6 @@ Run `revdep_details(, "DeclareDesign")` for more info Package suggested but not available for checking: ‘DesignLibrary’ ``` -# delayed - -
- -* Version: 0.4.0 -* GitHub: https://github.com/tlverse/delayed -* Source code: https://github.com/cran/delayed -* Date/Publication: 2022-10-19 22:25:09 UTC -* Number of recursive dependencies: 80 - -Run `revdep_details(, "delayed")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - # dipsaus
@@ -797,7 +505,7 @@ Run `revdep_details(, "dipsaus")` for more info * GitHub: https://github.com/marcozanotti/dispositionEffect * Source code: https://github.com/cran/dispositionEffect * Date/Publication: 2022-05-30 07:50:02 UTC -* Number of recursive dependencies: 135 +* Number of recursive dependencies: 136 Run `revdep_details(, "dispositionEffect")` for more info @@ -838,7 +546,7 @@ Run `revdep_details(, "dispositionEffect")` for more info * GitHub: https://github.com/sjspielman/dragon * Source code: https://github.com/cran/dragon * Date/Publication: 2022-04-08 08:42:33 UTC -* Number of recursive dependencies: 140 +* Number of recursive dependencies: 141 Run `revdep_details(, "dragon")` for more info @@ -846,36 +554,10 @@ Run `revdep_details(, "dragon")` for more info ## In both -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - -# drake - -
- -* Version: 7.13.4 -* GitHub: https://github.com/ropensci/drake -* Source code: https://github.com/cran/drake -* Date/Publication: 2022-08-19 15:40:02 UTC -* Number of recursive dependencies: 162 - -Run `revdep_details(, "drake")` for more info - -
- -## In both - -* checking package dependencies ... ERROR +* checking dependencies in R code ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + Namespace in Imports field not imported from: ‘htmltools’ + All declared Imports should be used. ``` # EFAtools @@ -896,9 +578,9 @@ Run `revdep_details(, "EFAtools")` for more info * checking installed package size ... NOTE ``` - installed size is 7.4Mb + installed size is 7.2Mb sub-directories of 1Mb or more: - libs 6.2Mb + libs 6.0Mb ``` * checking dependencies in R code ... NOTE @@ -944,33 +626,6 @@ Run `revdep_details(, "EpiNow2")` for more info
-## Newly fixed - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘case-studies.Rmd’ using rmarkdown - --- finished re-building ‘case-studies.Rmd’ - - --- re-building ‘estimate_infections.Rmd’ using rmarkdown - --- finished re-building ‘estimate_infections.Rmd’ - - --- re-building ‘estimate_secondary.Rmd’ using rmarkdown - --- finished re-building ‘estimate_secondary.Rmd’ - - ... - ConnectionTimeout - Error: processing vignette 'estimate_truncation.Rmd' failed with diagnostics: - pandoc document conversion failed with error 61 - --- failed re-building ‘estimate_truncation.Rmd’ - - SUMMARY: processing the following file failed: - ‘estimate_truncation.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - ## In both * checking installed package size ... NOTE @@ -994,7 +649,7 @@ Run `revdep_details(, "EpiNow2")` for more info * GitHub: https://github.com/EU-ECDC/epitweetr * Source code: https://github.com/cran/epitweetr * Date/Publication: 2022-12-01 00:40:03 UTC -* Number of recursive dependencies: 146 +* Number of recursive dependencies: 150 Run `revdep_details(, "epitweetr")` for more info @@ -1034,7 +689,7 @@ Run `revdep_details(, "fect")` for more info ``` installed size is 13.9Mb sub-directories of 1Mb or more: - libs 12.7Mb + libs 12.6Mb ``` * checking dependencies in R code ... NOTE @@ -1059,12 +714,18 @@ Run `revdep_details(, "flowGraph")` for more info ## In both -* checking package dependencies ... ERROR +* checking R code for possible problems ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + get_child: no visible binding for global variable ‘no_cores’ + get_paren: no visible binding for global variable ‘no_cores’ + ms_psig: no visible binding for global variable ‘meta’ + Undefined global functions or variables: + meta no_cores + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘doParallel’ ``` # foieGras @@ -1112,30 +773,6 @@ Run `revdep_details(, "forecastML")` for more info All declared Imports should be used. ``` -# genBaRcode - -
- -* Version: 1.2.5 -* GitHub: NA -* Source code: https://github.com/cran/genBaRcode -* Date/Publication: 2022-05-27 12:50:05 UTC -* Number of recursive dependencies: 158 - -Run `revdep_details(, "genBaRcode")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - # geocmeans
@@ -1154,7 +791,7 @@ Run `revdep_details(, "geocmeans")` for more info * checking installed package size ... NOTE ``` - installed size is 14.6Mb + installed size is 14.5Mb sub-directories of 1Mb or more: doc 1.7Mb extdata 3.0Mb @@ -1221,16 +858,11 @@ Run `revdep_details(, "greed")` for more info ## In both -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ - ``` - * checking installed package size ... NOTE ``` - installed size is 36.8Mb + installed size is 36.7Mb sub-directories of 1Mb or more: - libs 34.6Mb + libs 34.4Mb ``` * checking data for non-ASCII characters ... NOTE @@ -1371,12 +1003,17 @@ Run `revdep_details(, "infercnv")` for more info ## In both -* checking package dependencies ... ERROR +* checking installed package size ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + installed size is 5.1Mb + sub-directories of 1Mb or more: + extdata 3.1Mb + ``` + +* checking dependencies in R code ... NOTE + ``` + Unexported object imported by a ':::' call: ‘HiddenMarkov:::makedensity’ + See the note in ?`:::` about the use of this operator. ``` # inlinedocs @@ -1608,27 +1245,6 @@ Run `revdep_details(, "keyATM")` for more info libs 23.6Mb ``` -# lava - -
- -* Version: 1.7.1 -* GitHub: https://github.com/kkholst/lava -* Source code: https://github.com/cran/lava -* Date/Publication: 2023-01-06 22:30:34 UTC -* Number of recursive dependencies: 136 - -Run `revdep_details(, "lava")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ - ``` - # lidR
@@ -1672,7 +1288,7 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 253498 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 238761 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 ERROR Running the tests in ‘tests/testthat.R’ failed. @@ -1734,7 +1350,7 @@ Run `revdep_details(, "lightr")` for more info * GitHub: https://github.com/KechrisLab/MAI * Source code: https://github.com/cran/MAI * Date/Publication: 2022-11-01 -* Number of recursive dependencies: 168 +* Number of recursive dependencies: 171 Run `revdep_details(, "MAI")` for more info @@ -1802,7 +1418,7 @@ Run `revdep_details(, "mice")` for more info * GitHub: https://github.com/tidylab/microservices * Source code: https://github.com/cran/microservices * Date/Publication: 2022-10-01 09:50:02 UTC -* Number of recursive dependencies: 69 +* Number of recursive dependencies: 70 Run `revdep_details(, "microservices")` for more info @@ -1835,52 +1451,74 @@ Run `revdep_details(, "microservices")` for more info Execution halted ``` -# migraph +# MineICA
-* Version: 0.13.2 -* GitHub: https://github.com/snlab-ch/migraph -* Source code: https://github.com/cran/migraph -* Date/Publication: 2022-12-20 16:20:02 UTC -* Number of recursive dependencies: 137 +* Version: 1.38.0 +* GitHub: NA +* Source code: https://github.com/cran/MineICA +* Date/Publication: 2022-11-01 +* Number of recursive dependencies: 216 -Run `revdep_details(, "migraph")` for more info +Run `revdep_details(, "MineICA")` for more info
## In both -* checking package dependencies ... ERROR +* checking dependencies in R code ... WARNING ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + Namespace in Imports field not imported from: ‘lumiHumanAll.db’ + All declared Imports should be used. + Packages in Depends field not imported from: + ‘GOstats’ ‘Hmisc’ ‘JADE’ ‘RColorBrewer’ ‘Rgraphviz’ ‘annotate’ + ‘biomaRt’ ‘cluster’ ‘colorspace’ ‘fastICA’ ‘foreach’ ‘ggplot2’ + ‘graph’ ‘gtools’ ‘igraph’ ‘marray’ ‘mclust’ ‘methods’ ‘plyr’ ‘scales’ + ‘xtable’ + These packages need to be imported from (in the NAMESPACE file) + for when this namespace is loaded but not attached. + Missing or unexported object: ‘GOstats::geneIdsByCategory’ + ':::' calls which should be '::': + ‘Biobase:::annotation<-’ ‘Biobase:::validMsg’ ‘fpc:::pamk’ + ‘lumi:::getChipInfo’ ‘mclust:::adjustedRandIndex’ + See the note in ?`:::` about the use of this operator. + Unexported object imported by a ':::' call: ‘Biobase:::isValidVersion’ + See the note in ?`:::` about the use of this operator. ``` -# MineICA - -
- -* Version: 1.38.0 -* GitHub: NA -* Source code: https://github.com/cran/MineICA -* Date/Publication: 2022-11-01 -* Number of recursive dependencies: 217 - -Run `revdep_details(, "MineICA")` for more info - -
- -## In both - -* checking package dependencies ... ERROR +* checking Rd cross-references ... WARNING ``` - Package required but not available: ‘igraph’ + Missing link or links in documentation object 'Alist.Rd': + ‘class-IcaSet’ - Package suggested but not available for checking: ‘igraph’ + Missing link or links in documentation object 'Slist.Rd': + ‘class-IcaSet’ + Missing link or links in documentation object 'class-IcaSet.Rd': + ‘class-IcaSet’ + + Missing link or links in documentation object 'getComp.Rd': + ‘class-IcaSet’ + + Missing link or links in documentation object 'runAn.Rd': + ‘[Category:class-GOHyperGParams]{GOHyperGParams}’ + + See section 'Cross-references' in the 'Writing R Extensions' manual. + ``` + +* checking for missing documentation entries ... WARNING + ``` + Undocumented S4 classes: + ‘MineICAParams’ + All user-level objects in a package (including S4 classes and methods) + should have documentation entries. + See chapter ‘Writing R documentation files’ in the ‘Writing R + Extensions’ manual. + ``` + +* checking package dependencies ... NOTE + ``` Package which this enhances but not available for checking: ‘doMC’ Depends: includes the non-default packages: @@ -1890,9 +1528,63 @@ Run `revdep_details(, "MineICA")` for more info 'graph', 'annotate', 'Hmisc', 'fastICA', 'JADE' Adding so many packages to the search path is excessive and importing selectively is preferable. + ``` + +* checking DESCRIPTION meta-information ... NOTE + ``` + Packages listed in more than one of Depends, Imports, Suggests, Enhances: + ‘biomaRt’ ‘GOstats’ ‘cluster’ ‘mclust’ ‘igraph’ + A package should be listed in only one of these fields. + ``` + +* checking R code for possible problems ... NOTE + ``` + addGenesToGoReport: no visible global function definition for + ‘conditional’ + addGenesToGoReport: no visible global function definition for + ‘sigCategories’ + annot2Color: no visible global function definition for ‘brewer.pal’ + annot2Color: no visible global function definition for ‘heat_hcl’ + annot2Color: no visible global function definition for ‘terrain_hcl’ + annot2Color: no visible global function definition for ‘cm.colors’ + annot2Color: no visible global function definition for ‘rainbow_hcl’ + annotFeatures: no visible global function definition for ‘na.omit’ + ... + importFrom("methods", "callNextMethod", "new", "validObject") + importFrom("stats", "aggregate", "as.dendrogram", "as.dist", + "as.hclust", "chisq.test", "cor", "cor.test", "cutree", + "dist", "hclust", "kmeans", "kruskal.test", "lm", "median", + "na.omit", "order.dendrogram", "p.adjust", "quantile", + "reorder", "shapiro.test", "wilcox.test") + importFrom("utils", "capture.output", "combn", "read.table", + "write.table") + to your NAMESPACE file (and ensure that your DESCRIPTION Imports field + contains 'methods'). + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘MineICA.Rnw’ using Sweave + Loading required package: BiocGenerics - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + Attaching package: ‘BiocGenerics’ + + The following objects are masked from ‘package:stats’: + + IQR, mad, sd, var, xtabs + + ... + Error in { : task 2 failed - "Multiple cache results found. + Please clear your cache by running biomartCacheClear()" + + --- failed re-building ‘MineICA.Rnw’ + + SUMMARY: processing the following file failed: + ‘MineICA.Rnw’ + + Error: Vignette re-building failed. + Execution halted ``` # missSBM @@ -1911,22 +1603,21 @@ Run `revdep_details(, "missSBM")` for more info ## In both -* checking package dependencies ... ERROR +* checking installed package size ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + installed size is 9.7Mb + sub-directories of 1Mb or more: + libs 7.7Mb ``` # mistyR
-* Version: 1.6.0 +* Version: 1.6.1 * GitHub: https://github.com/saezlab/mistyR * Source code: https://github.com/cran/mistyR -* Date/Publication: 2022-11-01 +* Date/Publication: 2023-02-20 * Number of recursive dependencies: 152 Run `revdep_details(, "mistyR")` for more info @@ -1935,155 +1626,29 @@ Run `revdep_details(, "mistyR")` for more info ## In both -* checking examples ... ERROR - ``` - Running examples in ‘mistyR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_interaction_communities - > ### Title: Plot marker interaction communities - > ### Aliases: plot_interaction_communities - > - > ### ** Examples - > - > all.samples <- list.dirs("results", recursive = FALSE) - ... - - Collecting importances - - Aggregating - > - > misty.results %>% - + plot_interaction_communities("intra") %>% - + plot_interaction_communities("para.10") - Error: The provided result list is malformed. Consider using collect_results(). - Execution halted - ``` - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - - Computing triangulation - - Generating juxtaview - - Generating paraview - ... - 1. ├─testthat::expect_invisible(...) at test-plots.R:47:2 - 2. │ └─base::withVisible(call) - 3. ├─base::suppressWarnings(...) - 4. │ └─base::withCallingHandlers(...) - 5. └─mistyR::plot_interaction_communities(...) - 6. └─assertthat::assert_that(...) - - [ FAIL 1 | WARN 74 | SKIP 0 | PASS 172 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘mistyR.Rmd’ using rmarkdown - The magick package is required to crop "/c4/home/henrik/repositories/future/revdep/checks/mistyR/new/mistyR.Rcheck/vign_test/mistyR/vignettes/mistyR_files/figure-html/unnamed-chunk-2-1.png" but not available. - - Progress: ─────────────────────────────────────────────────────────────── 100% - Progress: ─────────────────────────────────────────────────────────────── 100% - Progress: ─────────────────────────────────────────────────────────────── 100% - Progress: ─────────────────────────────────────────────────────────────── 100% - Progress: ─────────────────────────────────────────────────────────────── 100% - Progress: ─────────────────────────────────────────────────────────────── 100% - ... - Quitting from lines 251-252 (mistyR.Rmd) - Error: processing vignette 'mistyR.Rmd' failed with diagnostics: - The package igraph (>= 1.2.7) is required to calculate the interaction communities. - --- failed re-building ‘mistyR.Rmd’ - - SUMMARY: processing the following file failed: - ‘mistyR.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ - ``` - -# mlr3pipelines - -
- -* Version: 0.4.2 -* GitHub: https://github.com/mlr-org/mlr3pipelines -* Source code: https://github.com/cran/mlr3pipelines -* Date/Publication: 2022-09-20 22:00:07 UTC -* Number of recursive dependencies: 159 - -Run `revdep_details(, "mlr3pipelines")` for more info - -
- -## In both - -* checking examples ... ERROR - ``` - Running examples in ‘mlr3pipelines-Ex.R’ failed - The error most likely occurred in: - - > ### Name: mlr_pipeops_imputelearner - > ### Title: Impute Features by Fitting a Learner - > ### Aliases: mlr_pipeops_imputelearner PipeOpImputeLearner - > - > ### ** Examples - > - > library("mlr3") - ... - Empty data.table (0 rows and 8 cols): .impute_col,age,glucose,insulin,pedigree,pregnant... - - $task_prototype - Empty data.table (0 rows and 8 cols): .impute_col,age,glucose,insulin,pedigree,pregnant... - - $mlr3_version - [1] ‘0.14.1’ - - $train_task - (768 x 8) - ``` - -* checking tests ... +* checking R code for possible problems ... NOTE ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - Starting 2 test processes - [ FAIL 5 | WARN 0 | SKIP 79 | PASS 12709 ] - - ══ Skipped tests ═══════════════════════════════════════════════════════════════ - • On CRAN (77) - • empty test (2) + aggregate_results: no visible binding for global variable ‘.data’ + aggregate_results_subset: no visible binding for global variable + ‘.data’ + bagged_mars_model: no visible binding for global variable ‘.data’ + collect_results : : no visible binding for global variable + ‘.data’ + collect_results: no visible binding for global variable ‘.data’ + collect_results : : : no visible binding for + global variable ‘.data’ + extract_signature: no visible binding for global variable ‘.data’ ... - Error: The following packages could not be loaded: igraph - Backtrace: - ▆ - 1. └─graph$plot() at test_multichannels.R:100:2 - 2. └─mlr3pipelines:::.__Graph__plot(...) - 3. └─mlr3misc::require_namespaces("igraph") - - [ FAIL 5 | WARN 0 | SKIP 79 | PASS 12709 ] - Error: Test failures - Execution halted - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ + plot_improvement_stats: no visible binding for global variable ‘.data’ + plot_interaction_communities: no visible binding for global variable + ‘.data’ + plot_interaction_heatmap: no visible binding for global variable + ‘.data’ + plot_view_contributions: no visible binding for global variable ‘.data’ + run_misty : : no visible binding for global variable ‘.data’ + svm_model: no visible binding for global variable ‘.data’ + Undefined global functions or variables: + .data ``` # momentuHMM @@ -2143,54 +1708,6 @@ Run `revdep_details(, "mslp")` for more info Execution halted ``` -# netShiny - -
- -* Version: 1.0 -* GitHub: NA -* Source code: https://github.com/cran/netShiny -* Date/Publication: 2022-08-22 09:30:02 UTC -* Number of recursive dependencies: 151 - -Run `revdep_details(, "netShiny")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - -# nncc - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/nncc -* Date/Publication: 2022-08-30 13:00:02 UTC -* Number of recursive dependencies: 82 - -Run `revdep_details(, "nncc")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - # oncomsm
@@ -2286,30 +1803,6 @@ Run `revdep_details(, "pavo")` for more info See ‘/c4/home/henrik/repositories/future/revdep/checks/pavo/new/pavo.Rcheck/00install.out’ for details. ``` -# pGRN - -
- -* Version: 0.3.5 -* GitHub: NA -* Source code: https://github.com/cran/pGRN -* Date/Publication: 2023-01-17 17:20:02 UTC -* Number of recursive dependencies: 93 - -Run `revdep_details(, "pGRN")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - # photosynthesis
@@ -2375,12 +1868,12 @@ Run `revdep_details(, "PLNmodels")` for more info ## In both -* checking package dependencies ... ERROR +* checking installed package size ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + installed size is 21.7Mb + sub-directories of 1Mb or more: + doc 2.1Mb + libs 18.3Mb ``` # portvine @@ -2476,48 +1969,6 @@ Run `revdep_details(, "prewas")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - 5. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 6. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) - 7. └─base (local) withOneRestart(expr, restarts[[1L]]) - 8. └─base (local) doWithOneRestart(return(expr), restart) - ── Error ('test-preprocess_tree_and_vcf.R:46'): root_tree roots tree and drops outgroup when given valid inputs ── - - ... - 2. ├─base::namespaceImportFrom(...) - 3. │ └─base::asNamespace(ns) - 4. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 5. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) - 6. └─base (local) withOneRestart(expr, restarts[[1L]]) - 7. └─base (local) doWithOneRestart(return(expr), restart) - - [ FAIL 4 | WARN 15 | SKIP 0 | PASS 324 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘getting_started_with_prewas.Rmd’ using rmarkdown - Quitting from lines 195-198 (getting_started_with_prewas.Rmd) - Error: processing vignette 'getting_started_with_prewas.Rmd' failed with diagnostics: - there is no package called 'igraph' - --- failed re-building ‘getting_started_with_prewas.Rmd’ - - SUMMARY: processing the following file failed: - ‘getting_started_with_prewas.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - * checking dependencies in R code ... NOTE ``` Namespace in Imports field not imported from: ‘stats’ @@ -2540,21 +1991,6 @@ Run `revdep_details(, "projpred")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(projpred) - This is projpred version 2.4.0. - > - > test_check("projpred") - Error: Package "rstanarm" is needed for these tests. Please install it. - Execution halted - ``` - * checking package dependencies ... NOTE ``` Package suggested but not available for checking: ‘cmdstanr’ @@ -2581,85 +2017,6 @@ Run `revdep_details(, "promises")` for more info 'LazyData' is specified without a 'data' directory ``` -# Prostar - -
- -* Version: 1.30.6 -* GitHub: https://github.com/prostarproteomics/Prostar -* Source code: https://github.com/cran/Prostar -* Date/Publication: 2023-02-17 -* Number of recursive dependencies: 166 - -Run `revdep_details(, "Prostar")` for more info - -
- -## In both - -* checking whether package ‘Prostar’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘Prostar’ ... -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘Prostar’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/new/Prostar.Rcheck/Prostar’ - - -``` -### CRAN - -``` -* installing *source* package ‘Prostar’ ... -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘Prostar’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/Prostar/old/Prostar.Rcheck/Prostar’ - - -``` -# protti - -
- -* Version: 0.6.0 -* GitHub: https://github.com/jpquast/protti -* Source code: https://github.com/cran/protti -* Date/Publication: 2023-01-20 10:30:02 UTC -* Number of recursive dependencies: 195 - -Run `revdep_details(, "protti")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ - ``` - # QDNAseq
@@ -2724,27 +2081,6 @@ Run `revdep_details(, "RAINBOWR")` for more info libs 36.5Mb ``` -# rangeMapper - -
- -* Version: 2.0.3 -* GitHub: https://github.com/mpio-be/rangeMapper -* Source code: https://github.com/cran/rangeMapper -* Date/Publication: 2022-10-03 22:20:02 UTC -* Number of recursive dependencies: 113 - -Run `revdep_details(, "rangeMapper")` for more info - -
- -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ - ``` - # regmedint
@@ -2753,7 +2089,7 @@ Run `revdep_details(, "rangeMapper")` for more info * GitHub: https://github.com/kaz-yos/regmedint * Source code: https://github.com/cran/regmedint * Date/Publication: 2022-04-06 20:20:02 UTC -* Number of recursive dependencies: 134 +* Number of recursive dependencies: 137 Run `revdep_details(, "regmedint")` for more info @@ -2844,66 +2180,6 @@ Run `revdep_details(, "sapfluxnetr")` for more info Note: found 4 marked UTF-8 strings ``` -# scBubbletree - -
- -* Version: 1.0.0 -* GitHub: https://github.com/snaketron/scBubbletree -* Source code: https://github.com/cran/scBubbletree -* Date/Publication: 2022-11-01 -* Number of recursive dependencies: 178 - -Run `revdep_details(, "scBubbletree")` for more info - -
- -## In both - -* checking whether package ‘scBubbletree’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘scBubbletree’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘scBubbletree’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/new/scBubbletree.Rcheck/scBubbletree’ - - -``` -### CRAN - -``` -* installing *source* package ‘scBubbletree’ ... -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘scBubbletree’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/scBubbletree/old/scBubbletree.Rcheck/scBubbletree’ - - -``` # scDiffCom
@@ -2912,7 +2188,7 @@ ERROR: lazy loading failed for package ‘scBubbletree’ * GitHub: NA * Source code: https://github.com/cran/scDiffCom * Date/Publication: 2021-08-17 07:20:05 UTC -* Number of recursive dependencies: 246 +* Number of recursive dependencies: 245 Run `revdep_details(, "scDiffCom")` for more info @@ -2920,36 +2196,6 @@ Run `revdep_details(, "scDiffCom")` for more info ## In both -* checking tests ... - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(scDiffCom) - > - > test_check("scDiffCom") - Loading required package: SeuratObject - ... - 6. ├─base::namespaceImportFrom(...) - 7. │ └─base::asNamespace(ns) - 8. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 9. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) - 10. └─base (local) withOneRestart(expr, restarts[[1L]]) - 11. └─base (local) doWithOneRestart(return(expr), restart) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 6 ] - Error: Test failures - Execution halted - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘igraph’ - ``` - * checking dependencies in R code ... NOTE ``` Namespaces in Imports field not imported from: @@ -3054,7 +2300,7 @@ Run `revdep_details(, "sentopics")` for more info installed size is 8.0Mb sub-directories of 1Mb or more: data 1.2Mb - libs 6.1Mb + libs 6.0Mb ``` * checking Rd cross-references ... NOTE @@ -3083,12 +2329,17 @@ Run `revdep_details(, "Seurat")` for more info ## In both -* checking package dependencies ... ERROR +* checking installed package size ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + installed size is 14.5Mb + sub-directories of 1Mb or more: + R 1.4Mb + libs 12.4Mb + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘Signac’ ``` # SeuratObject @@ -3172,7 +2423,7 @@ Run `revdep_details(, "shiny.worker")` for more info * GitHub: https://github.com/rvalieris/signeR * Source code: https://github.com/cran/signeR * Date/Publication: 2023-01-19 -* Number of recursive dependencies: 242 +* Number of recursive dependencies: 241 Run `revdep_details(, "signeR")` for more info @@ -3180,68 +2431,54 @@ Run `revdep_details(, "signeR")` for more info ## In both -* checking whether package ‘signeR’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘signeR’ ... -** using staged installation -** libs -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o -g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs -** R -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘signeR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/new/signeR.Rcheck/signeR’ - - -``` -### CRAN - -``` -* installing *source* package ‘signeR’ ... -** using staged installation -** libs -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fuzzy.cpp -o fuzzy.o -g++ -std=gnu++11 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c gibbs_2.cpp -o gibbs_2.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/signeR/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/signeR/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c signeR_init.c -o signeR_init.o -g++ -std=gnu++11 -shared -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -L/usr/local/lib64 -o signeR.so RcppExports.o fuzzy.o gibbs_2.o signeR_init.o -Wl,-S -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRlapack -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lRblas -lgfortran -lm -lquadmath -L/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/lib -lR -installing to /c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/00LOCK-signeR/00new/signeR/libs -** R -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘signeR’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/signeR/old/signeR.Rcheck/signeR’ - - -``` +* checking installed package size ... NOTE + ``` + installed size is 6.6Mb + sub-directories of 1Mb or more: + R 1.1Mb + doc 4.6Mb + ``` + +* checking R code for possible problems ... NOTE + ``` + covariate: no visible binding for global variable ‘.’ + denovo: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg19’ + denovo: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg38’ + explorepage: no visible binding for global variable ‘.’ + fitting: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg19’ + fitting: no visible binding for global variable + ‘BSgenome.Hsapiens.UCSC.hg38’ + ... + ExposureCorrelation,SignExp-numeric: no visible binding for global + variable ‘exposure’ + ExposureCorrelation,matrix-numeric: no visible binding for global + variable ‘Feature’ + ExposureCorrelation,matrix-numeric: no visible binding for global + variable ‘exposure’ + Undefined global functions or variables: + . BSgenome.Hsapiens.UCSC.hg19 BSgenome.Hsapiens.UCSC.hg38 Col Feature + Frequency Row Samples Signatures alt<- exposure fc project sig + sig_test + ``` + +* checking Rd files ... NOTE + ``` + prepare_Rd: cosmic_data.Rd:91-93: Dropping empty section \details + prepare_Rd: cosmic_data.Rd:98-100: Dropping empty section \references + prepare_Rd: cosmic_data.Rd:101-102: Dropping empty section \examples + prepare_Rd: tcga_similarities.Rd:96-98: Dropping empty section \details + prepare_Rd: tcga_similarities.Rd:99-101: Dropping empty section \source + prepare_Rd: tcga_similarities.Rd:102-104: Dropping empty section \references + prepare_Rd: tcga_similarities.Rd:105-106: Dropping empty section \examples + prepare_Rd: tcga_tumors.Rd:18-20: Dropping empty section \details + prepare_Rd: tcga_tumors.Rd:21-23: Dropping empty section \source + prepare_Rd: tcga_tumors.Rd:24-26: Dropping empty section \references + prepare_Rd: tcga_tumors.Rd:27-28: Dropping empty section \examples + ``` + # SimDesign
@@ -3301,7 +2538,7 @@ Run `revdep_details(, "skpr")` for more info * GitHub: https://github.com/talegari/solitude * Source code: https://github.com/cran/solitude * Date/Publication: 2021-07-29 20:00:02 UTC -* Number of recursive dependencies: 127 +* Number of recursive dependencies: 130 Run `revdep_details(, "solitude")` for more info @@ -3309,12 +2546,11 @@ Run `revdep_details(, "solitude")` for more info ## In both -* checking package dependencies ... ERROR +* checking dependencies in R code ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + Namespaces in Imports field not imported from: + ‘R6’ ‘lgr’ + All declared Imports should be used. ``` # spaMM @@ -3381,7 +2617,7 @@ Run `revdep_details(, "sparrpowR")` for more info * GitHub: https://github.com/NAU-CCL/SPARSEMODr * Source code: https://github.com/cran/SPARSEMODr * Date/Publication: 2022-07-19 20:50:02 UTC -* Number of recursive dependencies: 122 +* Number of recursive dependencies: 125 Run `revdep_details(, "SPARSEMODr")` for more info @@ -3450,30 +2686,6 @@ Run `revdep_details(, "spatialwarnings")` for more info libs 5.8Mb ``` -# specr - -
- -* Version: 1.0.0 -* GitHub: https://github.com/masurp/specr -* Source code: https://github.com/cran/specr -* Date/Publication: 2023-01-20 13:50:02 UTC -* Number of recursive dependencies: 149 - -Run `revdep_details(, "specr")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - # sphunif
@@ -3492,7 +2704,7 @@ Run `revdep_details(, "sphunif")` for more info * checking installed package size ... NOTE ``` - installed size is 24.2Mb + installed size is 24.1Mb sub-directories of 1Mb or more: libs 23.3Mb ``` @@ -3518,12 +2730,13 @@ Run `revdep_details(, "spNetwork")` for more info ## In both -* checking package dependencies ... ERROR +* checking installed package size ... NOTE ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. + installed size is 25.2Mb + sub-directories of 1Mb or more: + doc 1.0Mb + extdata 2.6Mb + libs 20.2Mb ``` # squat @@ -3558,7 +2771,7 @@ Run `revdep_details(, "squat")` for more info * GitHub: https://github.com/bcgov/ssdtools * Source code: https://github.com/cran/ssdtools * Date/Publication: 2022-05-14 23:50:02 UTC -* Number of recursive dependencies: 144 +* Number of recursive dependencies: 147 Run `revdep_details(, "ssdtools")` for more info @@ -3611,7 +2824,7 @@ Run `revdep_details(, "stars")` for more info * GitHub: NA * Source code: https://github.com/cran/synergyfinder * Date/Publication: 2023-02-13 -* Number of recursive dependencies: 191 +* Number of recursive dependencies: 193 Run `revdep_details(, "synergyfinder")` for more info @@ -3680,66 +2893,6 @@ Run `revdep_details(, "tableschema.r")` for more info Package unavailable to check Rd xrefs: ‘parsedate’ ``` -# tarchetypes - -
- -* Version: 0.7.4 -* GitHub: https://github.com/ropensci/tarchetypes -* Source code: https://github.com/cran/tarchetypes -* Date/Publication: 2023-01-06 18:50:20 UTC -* Number of recursive dependencies: 78 - -Run `revdep_details(, "tarchetypes")` for more info - -
- -## In both - -* checking whether package ‘tarchetypes’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘tarchetypes’ ... -** package ‘tarchetypes’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘tarchetypes’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/new/tarchetypes.Rcheck/tarchetypes’ - - -``` -### CRAN - -``` -* installing *source* package ‘tarchetypes’ ... -** package ‘tarchetypes’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘tarchetypes’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/tarchetypes/old/tarchetypes.Rcheck/tarchetypes’ - - -``` # targeted
@@ -3758,35 +2911,11 @@ Run `revdep_details(, "targeted")` for more info * checking installed package size ... NOTE ``` - installed size is 16.8Mb + installed size is 16.7Mb sub-directories of 1Mb or more: libs 15.7Mb ``` -# targets - -
- -* Version: 0.14.2 -* GitHub: https://github.com/ropensci/targets -* Source code: https://github.com/cran/targets -* Date/Publication: 2023-01-06 14:50:02 UTC -* Number of recursive dependencies: 173 - -Run `revdep_details(, "targets")` for more info - -
- -## In both - -* checking package dependencies ... ERROR - ``` - Package required but not available: ‘igraph’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - # text
@@ -3824,68 +2953,40 @@ Run `revdep_details(, "TreeSearch")` for more info ## In both -* checking whether package ‘TreeSearch’ can be installed ... ERROR - ``` - Installation failed. - See ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘TreeSearch’ ... -** package ‘TreeSearch’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘TreeSearch’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/new/TreeSearch.Rcheck/TreeSearch’ - - -``` -### CRAN - -``` -* installing *source* package ‘TreeSearch’ ... -** package ‘TreeSearch’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphy.c -o RMorphy.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RMorphyUtils.c -o RMorphyUtils.o -g++ -std=gnu++17 -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c TreeSearch-init.c -o TreeSearch-init.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c fitch.c -o fitch.o -gcc -I"/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/include" -DNDEBUG -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/Rcpp/include' -I'/c4/home/henrik/repositories/future/revdep/library/TreeSearch/TreeTools/include' -I/usr/local/include -fpic -g -O2 -c morphy.c -o morphy.o -... -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘TreeSearch’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/TreeSearch/old/TreeSearch.Rcheck/TreeSearch’ - - -``` +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + --- re-building ‘custom.Rmd’ using rmarkdown + Error reading bibliography file ../inst/REFERENCES.bib: + (line 401, column 1): + unexpected '@' + Error: processing vignette 'custom.Rmd' failed with diagnostics: + pandoc document conversion failed with error 25 + --- failed re-building ‘custom.Rmd’ + + --- re-building ‘getting-started.Rmd’ using rmarkdown + ... + Error: processing vignette 'tree-space.Rmd' failed with diagnostics: + pandoc document conversion failed with error 25 + --- failed re-building ‘tree-space.Rmd’ + + SUMMARY: processing the following files failed: + ‘custom.Rmd’ ‘profile-scores.Rmd’ ‘profile.Rmd’ ‘tree-search.Rmd’ + ‘tree-space.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.8Mb + sub-directories of 1Mb or more: + datasets 1.6Mb + doc 1.2Mb + libs 2.5Mb + ``` + # TriDimRegression
@@ -3929,7 +3030,7 @@ Run `revdep_details(, "TriDimRegression")` for more info * GitHub: https://github.com/RamiKrispin/TSstudio * Source code: https://github.com/cran/TSstudio * Date/Publication: 2020-01-21 05:30:02 UTC -* Number of recursive dependencies: 156 +* Number of recursive dependencies: 157 Run `revdep_details(, "TSstudio")` for more info @@ -3996,7 +3097,7 @@ Run `revdep_details(, "UCSCXenaShiny")` for more info * GitHub: https://github.com/dcgerard/updog * Source code: https://github.com/cran/updog * Date/Publication: 2022-10-18 08:00:02 UTC -* Number of recursive dependencies: 145 +* Number of recursive dependencies: 146 Run `revdep_details(, "updog")` for more info @@ -4006,7 +3107,7 @@ Run `revdep_details(, "updog")` for more info * checking installed package size ... NOTE ``` - installed size is 7.9Mb + installed size is 7.8Mb sub-directories of 1Mb or more: libs 7.1Mb ``` @@ -4027,54 +3128,13 @@ Run `revdep_details(, "vmeasur")` for more info ## In both -* checking whether package ‘vmeasur’ can be installed ... ERROR +* checking whether package ‘vmeasur’ can be installed ... WARNING ``` - Installation failed. + Found the following significant warnings: + Warning: no DISPLAY variable so Tk is not available See ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/00install.out’ for details. ``` -## Installation - -### Devel - -``` -* installing *source* package ‘vmeasur’ ... -** package ‘vmeasur’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘vmeasur’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/new/vmeasur.Rcheck/vmeasur’ - - -``` -### CRAN - -``` -* installing *source* package ‘vmeasur’ ... -** package ‘vmeasur’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘igraph’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘vmeasur’ -* removing ‘/c4/home/henrik/repositories/future/revdep/checks/vmeasur/old/vmeasur.Rcheck/vmeasur’ - - -``` # wru
@@ -4083,7 +3143,7 @@ ERROR: lazy loading failed for package ‘vmeasur’ * GitHub: https://github.com/kosukeimai/wru * Source code: https://github.com/cran/wru * Date/Publication: 2022-10-21 17:30:02 UTC -* Number of recursive dependencies: 87 +* Number of recursive dependencies: 89 Run `revdep_details(, "wru")` for more info @@ -4093,7 +3153,7 @@ Run `revdep_details(, "wru")` for more info * checking installed package size ... NOTE ``` - installed size is 5.6Mb + installed size is 5.5Mb sub-directories of 1Mb or more: data 3.5Mb libs 1.9Mb From 50edfe5644daebadeb681c924e25352791eef7d0 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 26 Feb 2023 00:11:00 +0100 Subject: [PATCH 69/88] Added optional assertion that no variables are added to the global environment by the future [#304] --- DESCRIPTION | 2 +- NAMESPACE | 3 ++ NEWS.md | 5 +++ R/FutureCondition-class.R | 35 +++++++++++++++++++ R/expressions.R | 10 ++++-- R/options.R | 10 ++++++ R/value.R | 72 ++++++++++++++++++++++++++++++--------- man/FutureCondition.Rd | 15 ++++++++ man/future.options.Rd | 6 ++++ 9 files changed, 139 insertions(+), 19 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 1b63e09e..efa9e672 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9009 +Version: 1.31.0-9010 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NAMESPACE b/NAMESPACE index 9f53a36b..73c449de 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -93,6 +93,9 @@ export(FutureGlobals) export(FutureMessage) export(FutureResult) export(FutureWarning) +export(GlobalEnvFutureCondition) +export(GlobalEnvFutureError) +export(GlobalEnvFutureWarning) export(MulticoreFuture) export(MultiprocessFuture) export(MultisessionFuture) diff --git a/NEWS.md b/NEWS.md index c6178d56..e950dd8a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ # Version (development version) +## New Features + + * Added optional assertion that no variables are added to the global + environment by the future. + ## Deprecated and Defunct * Add optional assertion of the internal Future `state` field. diff --git a/R/FutureCondition-class.R b/R/FutureCondition-class.R index fbe9557f..1eedc500 100644 --- a/R/FutureCondition-class.R +++ b/R/FutureCondition-class.R @@ -175,3 +175,38 @@ UnexpectedFutureResultError <- function(future, hint = NULL) { class(cond) <- class[!duplicated(class, fromLast = TRUE)] cond } + + + +#' @rdname FutureCondition +#' @export +GlobalEnvFutureCondition <- function(message = NULL, call = NULL, globalenv = globalenv, uuid = future$uuid, future = NULL) { + if (is.null(message)) { + label <- future$label + if (is.null(label)) label <- "" + message <- sprintf("Future (%s) added variables to the global environment. A future expression should never assign variables to the global environment - neither by assign() nor by <<-: [n=%d] %s", label, length(globalenv$added), paste(sQuote(globalenv$added), collapse = ", ")) + } + cond <- FutureCondition(message = message, call = call, uuid = uuid, future = future) + cond$globalenv <- globalenv + class <- c("GlobalEnvFutureCondition", class(cond)) + class(cond) <- class[!duplicated(class, fromLast = TRUE)] + cond +} + +#' @rdname FutureCondition +#' @export +GlobalEnvFutureWarning <- function(...) { + cond <- GlobalEnvFutureCondition(...) + class <- c("GlobalEnvFutureWarning", "FutureWarning", "warning", class(cond)) + class(cond) <- class[!duplicated(class, fromLast = TRUE)] + cond +} + +#' @rdname FutureCondition +#' @export +GlobalEnvFutureError <- function(...) { + cond <- GlobalEnvFutureCondition(...) + class <- c("GlobalEnvFutureError", "FutureError", "error", class(cond)) + class(cond) <- class[!duplicated(class, fromLast = TRUE)] + cond +} diff --git a/R/expressions.R b/R/expressions.R index 3c1c631e..aa97d19d 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -219,6 +219,9 @@ makeExpression <- local({ ...future.conditions <- base::list() ...future.rng <- base::globalenv()$.Random.seed + ## Record names of variables in the global environment + ...future.oldGlobalEnvNames <- names(base::globalenv()) + ## NOTE: We don't want to use local(body) w/ on.exit() because ## evaluation in a local is optional, cf. argument 'local'. ## If this was mandatory, we could. Instead we use @@ -226,7 +229,10 @@ makeExpression <- local({ ...future.result <- base::tryCatch({ base::withCallingHandlers({ ...future.value <- base::withVisible(.(expr)) - future::FutureResult(value = ...future.value$value, visible = ...future.value$visible, rng = !identical(base::globalenv()$.Random.seed, ...future.rng), started = ...future.startTime, version = "1.8") + ## Any variables added to the global environment? + added <- setdiff(names(base::globalenv()), ...future.oldGlobalEnvNames) + added <- setdiff(added, c("...future.value", "...future.oldGlobalEnvNames")) + future::FutureResult(value = ...future.value$value, visible = ...future.value$visible, rng = !identical(base::globalenv()$.Random.seed, ...future.rng), globalenv = list(added = added), started = ...future.startTime, version = "1.8") }, condition = base::local({ ## WORKAROUND: If the name of any of the below objects/functions ## coincides with a promise (e.g. a future assignment) then we @@ -371,7 +377,7 @@ makeExpression <- local({ enter <- bquote_apply(tmpl_enter_workdir) enter <- bquote_apply(tmpl_enter_optenvar) enter <- bquote_apply(tmpl_enter_future_opts) - + exit <- bquote_apply(tmpl_exit_future_opts) exit <- bquote_apply(tmpl_exit_optenvar) exit <- bquote_apply(tmpl_exit_workdir) diff --git a/R/options.R b/R/options.R index 3ea6aa74..578aa09c 100644 --- a/R/options.R +++ b/R/options.R @@ -46,6 +46,8 @@ #' #' \item{\option{future.rng.onMisuse}: (_beta feature - may change_)}{(character string) If random numbers are used in futures, then parallel (L'Ecuyer-CMRG) RNG should be used in order to get statistical sound RNGs. The defaults in the future framework assume that _no_ random number generation (RNG) is taken place in the future expression because L'Ecuyer-CMRG RNGs come with an unnecessary overhead if not needed. To protect against mistakes, the future framework attempts to detect when random numbers are used despite L'Ecuyer-CMRG RNGs are not in place. If this is detected, and `future.rng.onMisuse = "error"`, then an informative error message is produced. If `"warning"`, then a warning message is produced. If `"ignore"`, no check is performed. (Default: `"warning"`)} #' +#' \item{\option{future.globalenv.onMisuse}: (_beta feature - may change_)}{(character string) Assigning variables to the global environment for the purpose of using the variable at a later time makes no sense with futures, because the next future may be evaluated in different R process. To protect against mistakes, the future framework attempts to detect when variables are added to the global environment. If this is detected, and `future.globalenv.onMisuse = "error"`, then an informative error message is produced. If `"warning"`, then a warning message is produced. If `"ignore"`, no check is performed. (Default: `"ignore"`)} +#' #' \item{\option{future.wait.timeout}:}{(numeric) Maximum waiting time (in seconds) for a free worker before a timeout error is generated. (Default: `30 * 24 * 60 * 60` (= 30 days))} #' #' \item{\option{future.wait.interval}:}{(numeric) Initial interval (in @@ -151,6 +153,10 @@ #' future.plan #' R_FUTURE_PLAN #' future.resolve.recursive +#' R_FUTURE_RESOLVE_RECURSIVE +#' future.globalenv.onMisuse +#' R_FUTURE_GLOBALENV_ONMISUSE +#' future.rng.onMisuse #' R_FUTURE_RNG_ONMISUSE #' future.wait.alpha #' R_FUTURE_WAIT_ALPHA @@ -298,6 +304,10 @@ update_package_options <- function(debug = FALSE) { update_package_option("future.rng.onMisuse", debug = debug) update_package_option("future.rng.onMisuse.keepFuture", mode = "logical", debug = debug) + ## Prototyping in future 1.32.0: + update_package_option("future.globalenv.onMisuse", debug = debug) + update_package_option("future.globalenv.onMisuse.keepFuture", mode = "logical", debug = debug) + update_package_option("future.wait.timeout", mode = "numeric", debug = debug) update_package_option("future.wait.interval", mode = "numeric", debug = debug) update_package_option("future.wait.alpha", mode = "numeric", debug = debug) diff --git a/R/value.R b/R/value.R index 973c1692..4c838287 100644 --- a/R/value.R +++ b/R/value.R @@ -73,6 +73,46 @@ value.Future <- function(future, stdout = TRUE, signal = TRUE, ...) { } + ## Were there any variables added to the global enviroment? + if (length(result$globalenv$added) > 0L) { + onMisuse <- getOption("future.globalenv.onMisuse", "ignore") + if (onMisuse != "ignore") { + uuid <- future$uuid + if (getOption("future.rng.onMisuse.keepFuture", TRUE)) { + f <- future + } else { + f <- NULL + } + if (onMisuse == "error") { + cond <- GlobalEnvFutureError(globalenv = result$globalenv, uuid = uuid, future = f) + } else if (onMisuse == "warning") { + cond <- GlobalEnvFutureWarning(globalenv = result$globalenv, uuid = uuid, future = f) + } else { + cond <- NULL + warnf("Unknown value on option 'future.globalenv.onMisuse': %s", + sQuote(onMisuse)) + } + + if (!is.null(cond)) { + ## FutureCondition to stack of captured conditions + new <- list(condition = cond, signaled = FALSE) + conditions <- result$conditions + n <- length(conditions) + + ## An existing run-time error takes precedence + if (n > 0L && inherits(conditions[[n]]$condition, "error")) { + conditions[[n + 1L]] <- conditions[[n]] + conditions[[n]] <- new + } else { + conditions[[n + 1L]] <- new + } + + result$conditions <- conditions + future$result <- result + } + } + } + ## Was RNG used without requesting RNG seeds? if (!isTRUE(future$.rng_checked) && isFALSE(future$seed) && isTRUE(result$rng)) { @@ -87,8 +127,6 @@ value.Future <- function(future, stdout = TRUE, signal = TRUE, ...) { } else { onMisuse <- getOption("future.rng.onMisuse", "warning") if (onMisuse != "ignore") { - label <- future$label - if (is.null(label)) label <- "" cond <- RngFutureCondition(future = future) msg <- conditionMessage(cond) uuid <- future$uuid @@ -107,21 +145,23 @@ value.Future <- function(future, stdout = TRUE, signal = TRUE, ...) { sQuote(onMisuse)) } - ## RngFutureCondition to stack of captured conditions - new <- list(condition = cond, signaled = FALSE) - conditions <- result$conditions - n <- length(conditions) - - ## An existing run-time error takes precedence - if (n > 0L && inherits(conditions[[n]]$condition, "error")) { - conditions[[n + 1L]] <- conditions[[n]] - conditions[[n]] <- new - } else { - conditions[[n + 1L]] <- new + if (!is.null(cond)) { + ## RngFutureCondition to stack of captured conditions + new <- list(condition = cond, signaled = FALSE) + conditions <- result$conditions + n <- length(conditions) + + ## An existing run-time error takes precedence + if (n > 0L && inherits(conditions[[n]]$condition, "error")) { + conditions[[n + 1L]] <- conditions[[n]] + conditions[[n]] <- new + } else { + conditions[[n + 1L]] <- new + } + + result$conditions <- conditions + future$result <- result } - - result$conditions <- conditions - future$result <- result } } } diff --git a/man/FutureCondition.Rd b/man/FutureCondition.Rd index 58b9b8ce..5d06cf15 100644 --- a/man/FutureCondition.Rd +++ b/man/FutureCondition.Rd @@ -9,6 +9,9 @@ \alias{RngFutureWarning} \alias{RngFutureError} \alias{UnexpectedFutureResultError} +\alias{GlobalEnvFutureCondition} +\alias{GlobalEnvFutureWarning} +\alias{GlobalEnvFutureError} \title{A condition (message, warning, or error) that occurred while orchestrating a future} \usage{ FutureCondition(message, call = NULL, uuid = future$uuid, future = NULL) @@ -31,6 +34,18 @@ RngFutureWarning(...) RngFutureError(...) UnexpectedFutureResultError(future, hint = NULL) + +GlobalEnvFutureCondition( + message = NULL, + call = NULL, + globalenv = globalenv, + uuid = future$uuid, + future = NULL +) + +GlobalEnvFutureWarning(...) + +GlobalEnvFutureError(...) } \arguments{ \item{message}{A message condition.} diff --git a/man/future.options.Rd b/man/future.options.Rd index 71103654..b21b0246 100644 --- a/man/future.options.Rd +++ b/man/future.options.Rd @@ -27,6 +27,10 @@ \alias{future.plan} \alias{R_FUTURE_PLAN} \alias{future.resolve.recursive} +\alias{R_FUTURE_RESOLVE_RECURSIVE} +\alias{future.globalenv.onMisuse} +\alias{R_FUTURE_GLOBALENV_ONMISUSE} +\alias{future.rng.onMisuse} \alias{R_FUTURE_RNG_ONMISUSE} \alias{future.wait.alpha} \alias{R_FUTURE_WAIT_ALPHA} @@ -87,6 +91,8 @@ If \code{"ignore"}, no scan is performed. \item{\option{future.rng.onMisuse}: (\emph{beta feature - may change})}{(character string) If random numbers are used in futures, then parallel (L'Ecuyer-CMRG) RNG should be used in order to get statistical sound RNGs. The defaults in the future framework assume that \emph{no} random number generation (RNG) is taken place in the future expression because L'Ecuyer-CMRG RNGs come with an unnecessary overhead if not needed. To protect against mistakes, the future framework attempts to detect when random numbers are used despite L'Ecuyer-CMRG RNGs are not in place. If this is detected, and \code{future.rng.onMisuse = "error"}, then an informative error message is produced. If \code{"warning"}, then a warning message is produced. If \code{"ignore"}, no check is performed. (Default: \code{"warning"})} +\item{\option{future.globalenv.onMisuse}: (\emph{beta feature - may change})}{(character string) Assigning variables to the global environment for the purpose of using the variable at a later time makes no sense with futures, because the next future may be evaluated in different R process. To protect against mistakes, the future framework attempts to detect when variables are added to the global environment. If this is detected, and \code{future.globalenv.onMisuse = "error"}, then an informative error message is produced. If \code{"warning"}, then a warning message is produced. If \code{"ignore"}, no check is performed. (Default: \code{"ignore"})} + \item{\option{future.wait.timeout}:}{(numeric) Maximum waiting time (in seconds) for a free worker before a timeout error is generated. (Default: \code{30 * 24 * 60 * 60} (= 30 days))} \item{\option{future.wait.interval}:}{(numeric) Initial interval (in From 9f98891b3346e9a3df70688c75c28a4bb2f4c762 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 26 Feb 2023 00:31:05 +0100 Subject: [PATCH 70/88] Add option 'future.onFutureCondition.keepFuture' (and remove hidden option 'future.rng.onMisuse.keepFuture') --- DESCRIPTION | 2 +- NEWS.md | 4 ++++ R/FutureCondition-class.R | 4 ++++ R/options.R | 9 +++++++-- R/value.R | 22 ++++------------------ man/future.options.Rd | 4 ++++ 6 files changed, 24 insertions(+), 21 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index efa9e672..43b1b657 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9010 +Version: 1.31.0-9011 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NEWS.md b/NEWS.md index e950dd8a..35f99d43 100644 --- a/NEWS.md +++ b/NEWS.md @@ -5,6 +5,10 @@ * Added optional assertion that no variables are added to the global environment by the future. + * Add option `future.onFutureCondition.keepFuture` for controlling + whether `FutureCondition` objects should have a copy of the + `Future` object or not. + ## Deprecated and Defunct * Add optional assertion of the internal Future `state` field. diff --git a/R/FutureCondition-class.R b/R/FutureCondition-class.R index 1eedc500..23f5dc40 100644 --- a/R/FutureCondition-class.R +++ b/R/FutureCondition-class.R @@ -45,6 +45,10 @@ FutureCondition <- function(message, call = NULL, uuid = future$uuid, future = N stop_if_not(is.character(uuid), length(uuid) == 1L, !is.na(uuid)) } if (!is.null(future)) stop_if_not(inherits(future, "Future")) + + if (!getOption("future.onFutureCondition.keepFuture", TRUE)) { + future <- NULL + } ## Create a condition object class <- c("FutureCondition", class) diff --git a/R/options.R b/R/options.R index 578aa09c..4f96ba9f 100644 --- a/R/options.R +++ b/R/options.R @@ -48,6 +48,8 @@ #' #' \item{\option{future.globalenv.onMisuse}: (_beta feature - may change_)}{(character string) Assigning variables to the global environment for the purpose of using the variable at a later time makes no sense with futures, because the next future may be evaluated in different R process. To protect against mistakes, the future framework attempts to detect when variables are added to the global environment. If this is detected, and `future.globalenv.onMisuse = "error"`, then an informative error message is produced. If `"warning"`, then a warning message is produced. If `"ignore"`, no check is performed. (Default: `"ignore"`)} #' +#' \item{\option{future.onFutureCondition.keepFuture}:}{(logical) If `TRUE`, a `FutureCondition` keeps a copy of the `Future` object that triggered the condition. If `FALSE`, it is dropped. (Default: `TRUE`)} +#' #' \item{\option{future.wait.timeout}:}{(numeric) Maximum waiting time (in seconds) for a free worker before a timeout error is generated. (Default: `30 * 24 * 60 * 60` (= 30 days))} #' #' \item{\option{future.wait.interval}:}{(numeric) Initial interval (in @@ -152,6 +154,8 @@ #' R_FUTURE_GLOBALS_ONREFERENCE #' future.plan #' R_FUTURE_PLAN +#' future.onFutureCondition.keepFuture +#' R_FUTURE_ONFUTURECONDITION_KEEPFUTURE #' future.resolve.recursive #' R_FUTURE_RESOLVE_RECURSIVE #' future.globalenv.onMisuse @@ -301,12 +305,13 @@ update_package_options <- function(debug = FALSE) { update_package_option(name, mode = "numeric", debug = debug) } + ## Introduced in future 1.32.0: + update_package_option("future.onFutureCondition.keepFuture", mode = "logical", debug = debug) + update_package_option("future.rng.onMisuse", debug = debug) - update_package_option("future.rng.onMisuse.keepFuture", mode = "logical", debug = debug) ## Prototyping in future 1.32.0: update_package_option("future.globalenv.onMisuse", debug = debug) - update_package_option("future.globalenv.onMisuse.keepFuture", mode = "logical", debug = debug) update_package_option("future.wait.timeout", mode = "numeric", debug = debug) update_package_option("future.wait.interval", mode = "numeric", debug = debug) diff --git a/R/value.R b/R/value.R index 4c838287..dc7045e2 100644 --- a/R/value.R +++ b/R/value.R @@ -77,16 +77,10 @@ value.Future <- function(future, stdout = TRUE, signal = TRUE, ...) { if (length(result$globalenv$added) > 0L) { onMisuse <- getOption("future.globalenv.onMisuse", "ignore") if (onMisuse != "ignore") { - uuid <- future$uuid - if (getOption("future.rng.onMisuse.keepFuture", TRUE)) { - f <- future - } else { - f <- NULL - } if (onMisuse == "error") { - cond <- GlobalEnvFutureError(globalenv = result$globalenv, uuid = uuid, future = f) + cond <- GlobalEnvFutureError(globalenv = result$globalenv, future = future) } else if (onMisuse == "warning") { - cond <- GlobalEnvFutureWarning(globalenv = result$globalenv, uuid = uuid, future = f) + cond <- GlobalEnvFutureWarning(globalenv = result$globalenv, future = future) } else { cond <- NULL warnf("Unknown value on option 'future.globalenv.onMisuse': %s", @@ -127,18 +121,10 @@ value.Future <- function(future, stdout = TRUE, signal = TRUE, ...) { } else { onMisuse <- getOption("future.rng.onMisuse", "warning") if (onMisuse != "ignore") { - cond <- RngFutureCondition(future = future) - msg <- conditionMessage(cond) - uuid <- future$uuid - if (getOption("future.rng.onMisuse.keepFuture", TRUE)) { - f <- future - } else { - f <- NULL - } if (onMisuse == "error") { - cond <- RngFutureError(msg, uuid = uuid, future = f) + cond <- RngFutureError(future = future) } else if (onMisuse == "warning") { - cond <- RngFutureWarning(msg, uuid = uuid, future = f) + cond <- RngFutureWarning(future = future) } else { cond <- NULL warnf("Unknown value on option 'future.rng.onMisuse': %s", diff --git a/man/future.options.Rd b/man/future.options.Rd index b21b0246..1cafcdbc 100644 --- a/man/future.options.Rd +++ b/man/future.options.Rd @@ -26,6 +26,8 @@ \alias{R_FUTURE_GLOBALS_ONREFERENCE} \alias{future.plan} \alias{R_FUTURE_PLAN} +\alias{future.onFutureCondition.keepFuture} +\alias{R_FUTURE_ONFUTURECONDITION_KEEPFUTURE} \alias{future.resolve.recursive} \alias{R_FUTURE_RESOLVE_RECURSIVE} \alias{future.globalenv.onMisuse} @@ -93,6 +95,8 @@ If \code{"ignore"}, no scan is performed. \item{\option{future.globalenv.onMisuse}: (\emph{beta feature - may change})}{(character string) Assigning variables to the global environment for the purpose of using the variable at a later time makes no sense with futures, because the next future may be evaluated in different R process. To protect against mistakes, the future framework attempts to detect when variables are added to the global environment. If this is detected, and \code{future.globalenv.onMisuse = "error"}, then an informative error message is produced. If \code{"warning"}, then a warning message is produced. If \code{"ignore"}, no check is performed. (Default: \code{"ignore"})} +\item{\option{future.onFutureCondition.keepFuture}:}{(logical) If \code{TRUE}, a \code{FutureCondition} keeps a copy of the \code{Future} object that triggered the condition. If \code{FALSE}, it is dropped. (Default: \code{TRUE})} + \item{\option{future.wait.timeout}:}{(numeric) Maximum waiting time (in seconds) for a free worker before a timeout error is generated. (Default: \code{30 * 24 * 60 * 60} (= 30 days))} \item{\option{future.wait.interval}:}{(numeric) Initial interval (in From b39922bc953341defb2fcb7d44c2ba5ca41aaf4a Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 26 Feb 2023 01:30:34 +0100 Subject: [PATCH 71/88] AD-HOC WORKAROUND: The future.tests checks on %<-% with lazy=TRUE gives an error on "promise already under evaluation: recursive default argument reference or earlier problems?" with the new scan-for-global-variables. It happened when calling names(globalenv()), which is odd. This error looked very similar to the future.tests that failed on MS Windows the other day [#304] --- DESCRIPTION | 2 +- R/expressions.R | 20 +++++++++++++------- 2 files changed, 14 insertions(+), 8 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 43b1b657..c1b0eb83 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9011 +Version: 1.31.0-9012 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/expressions.R b/R/expressions.R index aa97d19d..eae736f7 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -219,8 +219,10 @@ makeExpression <- local({ ...future.conditions <- base::list() ...future.rng <- base::globalenv()$.Random.seed - ## Record names of variables in the global environment - ...future.oldGlobalEnvNames <- names(base::globalenv()) + if (.(globalenv)) { + ## Record names of variables in the global environment + ...future.globalenv.names <- c(base::names(base::.GlobalEnv), "...future.value", "...future.globalenv.names") + } ## NOTE: We don't want to use local(body) w/ on.exit() because ## evaluation in a local is optional, cf. argument 'local'. @@ -229,10 +231,14 @@ makeExpression <- local({ ...future.result <- base::tryCatch({ base::withCallingHandlers({ ...future.value <- base::withVisible(.(expr)) - ## Any variables added to the global environment? - added <- setdiff(names(base::globalenv()), ...future.oldGlobalEnvNames) - added <- setdiff(added, c("...future.value", "...future.oldGlobalEnvNames")) - future::FutureResult(value = ...future.value$value, visible = ...future.value$visible, rng = !identical(base::globalenv()$.Random.seed, ...future.rng), globalenv = list(added = added), started = ...future.startTime, version = "1.8") + future::FutureResult( + value = ...future.value$value, + visible = ...future.value$visible, + rng = !identical(base::globalenv()$.Random.seed, ...future.rng), + globalenv = if (.(globalenv)) list(added = base::setdiff(base::names(base::.GlobalEnv), ...future.globalenv.names)) else NULL, + started = ...future.startTime, + version = "1.8" + ) }, condition = base::local({ ## WORKAROUND: If the name of any of the below objects/functions ## coincides with a promise (e.g. a future assignment) then we @@ -347,7 +353,7 @@ makeExpression <- local({ }) - function(expr, local = TRUE, immediateConditions = FALSE, stdout = TRUE, conditionClasses = NULL, split = FALSE, globals.onMissing = getOption("future.globals.onMissing", NULL), enter = NULL, exit = NULL, version = "1.8") { + function(expr, local = TRUE, immediateConditions = FALSE, stdout = TRUE, conditionClasses = NULL, split = FALSE, globals.onMissing = getOption("future.globals.onMissing", NULL), globalenv = (getOption("future.globalenv.onMisuse", "ignore") != "ignore"), enter = NULL, exit = NULL, version = "1.8") { conditionClassesExclude <- attr(conditionClasses, "exclude", exact = TRUE) muffleInclude <- attr(conditionClasses, "muffleInclude", exact = TRUE) if (is.null(muffleInclude)) muffleInclude <- "^muffle" From 1b8d235ee94a717d04d6a403595e08aed083a268 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sun, 26 Feb 2023 01:46:34 +0100 Subject: [PATCH 72/88] Allow .Random.seed to be added [#304] --- R/expressions.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/expressions.R b/R/expressions.R index eae736f7..c7ae602f 100644 --- a/R/expressions.R +++ b/R/expressions.R @@ -221,7 +221,7 @@ makeExpression <- local({ if (.(globalenv)) { ## Record names of variables in the global environment - ...future.globalenv.names <- c(base::names(base::.GlobalEnv), "...future.value", "...future.globalenv.names") + ...future.globalenv.names <- c(base::names(base::.GlobalEnv), "...future.value", "...future.globalenv.names", ".Random.seed") } ## NOTE: We don't want to use local(body) w/ on.exit() because From 14f4bfa2d718050f5b10d00e993ffc4fde4e49bb Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 27 Feb 2023 09:42:58 +0100 Subject: [PATCH 73/88] NEWS: tweak [ci skip] --- NEWS.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/NEWS.md b/NEWS.md index 35f99d43..f86ae0ed 100644 --- a/NEWS.md +++ b/NEWS.md @@ -2,8 +2,8 @@ ## New Features - * Added optional assertion that no variables are added to the global - environment by the future. + * Added optional assertion against adding variables to the global + environment by a future. * Add option `future.onFutureCondition.keepFuture` for controlling whether `FutureCondition` objects should have a copy of the From 3782ba0bc65cbe9eb2562ed8612962bed90e4a60 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 27 Feb 2023 14:30:00 +0100 Subject: [PATCH 74/88] GHA: Relax assertion for R (< 3.5.0), because of some hiccup in some dependancy --- .github/workflows/R-CMD-check.yaml | 1 + 1 file changed, 1 insertion(+) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index 8559cbdd..e4af93e1 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -112,6 +112,7 @@ jobs: if: runner.os == 'Windows' run: | rcmdcheck::rcmdcheck( + build_args = if (getRversion() < "3.5.0") "--no-build-vignettes", args = c("--no-manual", "--as-cran", if (.Platform$OS.type == "windows" && getRversion() >= "4.2.0") "--no-multiarch"), check_dir = "check" ) From be75d1000be8377380fbef8ae484bf1af4bacf29 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 27 Feb 2023 11:13:24 -0800 Subject: [PATCH 75/88] REVDEP: 280 revdep packages for branch feature/journal [ci skip] --- revdep/README.md | 577 +++++++++++++++++++++++---------------------- revdep/problems.md | 58 ++++- 2 files changed, 341 insertions(+), 294 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 70ac5b47..c584d773 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,14 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-25 | +|date |2023-02-27 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9009 |* | +|future |1.31.0 |1.31.0-9112 |* | |codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -26,294 +26,295 @@ # Revdeps -## New problems (1) +## New problems (2) -|package |version |error |warning |note | -|:-------|:-------|:------|:-------|:----| -|[civis](problems.md#civis)|3.1.0 |__+1__ | | | +|package |version |error |warning |note | +|:-------|:-------|:--------|:-------|:----| +|[civis](problems.md#civis)|3.1.0 |__+1__ | | | +|[MineICA](problems.md#mineica)|1.38.0 |1 __+1__ |3 |4 | ## All (280) -|package |version |error |warning |note | -|:------------------------|:---------|:------|:-------|:----| -|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | -|alookr |0.3.7 | | | | -|alphaci |1.0.0 | | | | -|AlpsNMR |4.0.4 | | | | -|arkdb |0.0.16 | | | | -|aroma.affymetrix |3.2.1 | | | | -|aroma.cn |1.7.0 | | | | -|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | -|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | -|bamm |0.4.3 | | | | -|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | -|BatchGetSymbols |2.6.4 | | | | -|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | -|bayesian |0.0.9 | | | | -|bayesmove |0.2.1 | | | | -|bcmaps |1.1.0 | | | | -|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | -|bhmbasket |0.9.5 | | | | -|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | -|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | -|bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan)|0.4-6 | | |3 | -|bolasso |0.2.0 | | | | -|[brms](problems.md#brms) |2.18.0 | | |2 | -|brpop |0.1.5 | | | | -|canaper |1.0.0 | | | | -|ceRNAnetsim |1.10.0 | | | | -|cft |1.0.0 | | | | -|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | -|[civis](problems.md#civis)|3.1.0 |__+1__ | | | -|Clustering |1.7.7 | | | | -|codalm |0.1.2 | | | | -|[codebook](problems.md#codebook)|0.9.2 | | |3 | -|conformalInference.fd |1.1.1 | | | | -|conformalInference.multi |1.1.1 | | | | -|crossmap |0.4.0 | | | | -|CSCNet |0.1.2 | | | | -|[cSEM](problems.md#csem) |0.5.0 | | |1 | -|[CSGo](problems.md#csgo) |0.6.7 | | |1 | -|cvCovEst |1.2.0 | | | | -|dagHMM |0.1.0 | | | | -|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | -|delayed |0.4.0 | | | | -|dhReg |0.1.1 | | | | -|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | -|disk.frame |0.8.0 | | | | -|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | -|doFuture |0.12.2 | | | | -|DQAstats |0.3.2 | | | | -|[dragon](problems.md#dragon)|1.2.1 | | |1 | -|drake |7.13.4 | | | | -|drimmR |1.0.1 | | | | -|drtmle |1.1.2 | | | | -|dsos |0.1.2 | | | | -|DT |0.27 | | | | -|easyalluvial |0.3.1 | | | | -|ecic |0.0.3 | | | | -|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | -|elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.17 | |1 | | -|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | -|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | -|epwshiftr |0.1.3 | | | | -|ezcox |1.0.2 | | | | -|fabletools |0.3.2 | | | | -|FAMoS |0.3.0 | | | | -|fastRhockey |0.4.0 | | | | -|[fect](problems.md#fect) |1.0.0 | | |2 | -|fiery |1.1.4 | | | | -|finbif |0.7.2 | | | | -|fitlandr |0.1.0 | | | | -|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | -|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | -|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | -|fst4pg |1.0.0 | | | | -|fundiversity |1.1.1 | | | | -|funGp |0.3.1 | | | | -|furrr |0.3.1 | | | | -|future.apply |1.10.0 | | | | -|future.batchtools |0.12.0 | | | | -|future.callr |0.8.1 | | | | -|future.tests |0.5.0 | | | | -|fxTWAPLS |0.1.2 | | | | -|genBaRcode |1.2.5 | | | | -|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | -|GetBCBData |0.7.0 | | | | -|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | -|googlePubsubR |0.0.3 | | | | -|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | -|[greed](problems.md#greed)|0.6.1 | | |2 | -|greta |0.4.3 | | | | -|gstat |2.1-0 | | | | -|GSVA |1.46.0 | | | | -|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | -|gtfs2emis |0.1.0 | | | | -|gtfs2gps |2.1-0 | | | | -|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | -|hacksig |0.1.2 | | | | -|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | -|haldensify |0.2.3 | | | | -|hoopR |1.8.0 | | | | -|[hwep](problems.md#hwep) |2.0.0 | | |2 | -|idmodelr |0.4.0 | | | | -|imagefluency |0.2.4 | | | | -|iml |0.11.1 | | | | -|incubate |1.2.0 | | | | -|[infercnv](problems.md#infercnv)|1.14.0 | | |2 | -|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | -|[InPAS](problems.md#inpas)|2.6.0 | | |1 | -|[interflex](problems.md#interflex)|1.2.6 | | |1 | -|ipc |0.1.4 | | | | -|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | -|isopam |1.1.0 | | | | -|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | -|JointAI |1.0.4 | | | | -|jstor |0.3.10 | | | | -|JuliaConnectoR |1.1.1 | | | | -|kernelboot |0.1.9 | | | | -|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | -|latentcor |2.0.1 | | | | -|lava |1.7.2 | | | | -|ldaPrototype |0.3.1 | | | | -|ldsr |0.0.2 | | | | -|lemna |1.0.0 | | | | -|LexFindR |1.0.2 | | | | -|lgr |0.4.4 | | | | -|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | -|[lightr](problems.md#lightr)|1.7.0 | | |2 | -|lmtp |1.3.1 | | | | -|LWFBrook90R |0.5.2 | | | | -|[MAI](problems.md#mai) |1.4.0 | | |1 | -|MAMS |2.0.0 | | | | -|marginaleffects |0.10.0 | | | | -|mcmcensemble |3.0.0 | | | | -|mcp |0.3.2 | | | | -|merTools |0.5.2 | | | | -|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | -|[mice](problems.md#mice) |3.15.0 | |1 | | -|[microservices](problems.md#microservices)|0.2.0 |1 | | | -|microSTASIS |0.1.0 | | | | -|migraph |0.13.2 | | | | -|mikropml |1.5.0 | | | | -|[MineICA](problems.md#mineica)|1.38.0 | |3 |4 | -|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | -|[mistyR](problems.md#mistyr)|1.6.1 | | |1 | -|mlr3 |0.14.1 | | | | -|mlr3db |0.5.0 | | | | -|mlr3pipelines |0.4.2 | | | | -|mlr3spatial |0.3.1 | | | | -|modelsummary |1.3.0 | | | | -|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | -|MOSS |0.2.2 | | | | -|mrgsim.parallel |0.2.1 | | | | -|[mslp](problems.md#mslp) |1.0.1 |1 | | | -|multiverse |0.6.1 | | | | -|netShiny |1.0 | | | | -|NetSimR |0.1.2 | | | | -|nfl4th |1.0.2 | | | | -|nflfastR |4.5.1 | | | | -|nflseedR |1.2.0 | | | | -|nncc |1.0.0 | | | | -|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | -|onemapsgapi |1.1.0 | | | | -|[OOS](problems.md#oos) |1.0.0 | | |1 | -|origami |1.0.7 | | | | -|paramsim |0.1.0 | | | | -|[partR2](problems.md#partr2)|0.9.1 | | |1 | -|[pavo](problems.md#pavo) |2.8.0 | |1 | | -|pbapply |1.7-0 | | | | -|PCRedux |1.1-2 | | | | -|PeakSegDisk |2022.2.1 | | | | -|penaltyLearning |2020.5.13 | | | | -|pGRN |0.3.5 | | | | -|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | -|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | -|PINstimation |0.1.1 | | | | -|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | -|plumber |1.2.1 | | | | -|polle |1.2 | | | | -|POMADE |0.1.0 | | | | -|[portvine](problems.md#portvine)|1.0.2 | | |1 | -|powRICLPM |0.1.1 | | | | -|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | -|[prewas](problems.md#prewas)|1.1.1 | | |1 | -|progressr |0.13.0 | | | | -|[projpred](problems.md#projpred)|2.4.0 | | |1 | -|[promises](problems.md#promises)|1.2.0.1 | | |1 | -|Prostar |1.30.7 | | | | -|protti |0.6.0 | | | | -|PSCBS |0.66.0 | | | | -|PUMP |1.0.1 | | | | -|qape |2.0 | | | | -|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | -|qgcomp |2.10.1 | | | | -|qgcompint |0.7.0 | | | | -|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | -|rangeMapper |2.0.3 | | | | -|rBiasCorrection |0.3.4 | | | | -|receptiviti |0.1.3 | | | | -|refineR |1.5.1 | | | | -|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | -|remiod |1.0.2 | | | | -|reproducible |1.2.16 |-1 | | | -|reval |3.1-0 | | | | -|[rgee](problems.md#rgee) |1.1.5 | | |2 | -|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | -|robust2sls |0.2.2 | | | | -|RTransferEntropy |0.2.21 | | | | -|s3fs |0.1.2 | | | | -|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | -|scBubbletree |1.0.0 | | | | -|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | -|SCtools |0.3.2.1 | | | | -|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | -|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | -|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | -|seer |1.1.8 | | | | -|semtree |0.9.18 | | | | -|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | -|[Seurat](problems.md#seurat)|4.3.0 | | |2 | -|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | -|[shiny](problems.md#shiny)|1.7.4 | | |1 | -|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | -|sigminer |2.1.9 | | | | -|Signac |1.9.0 | | | | -|[signeR](problems.md#signer)|2.0.2 | | |3 | -|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | -|simfinapi |0.2.0 | | | | -|simglm |0.8.9 | | | | -|simhelpers |0.1.2 | | | | -|sims |0.0.3 | | | | -|skewlmm |1.0.0 | | | | -|[skpr](problems.md#skpr) |1.1.6 | | |1 | -|smoots |1.1.3 | | | | -|sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude)|1.1.3 | | |1 | -|sovereign |1.2.1 | | | | -|[spaMM](problems.md#spamm)|4.1.20 | | |2 | -|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | -|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | -|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | -|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | -|specr |1.0.0 | | | | -|sperrorest |3.0.5 | | | | -|spFSR |2.0.3 | | | | -|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | -|[squat](problems.md#squat)|0.1.0 | | |1 | -|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | -|[stars](problems.md#stars)|0.6-0 | | |2 | -|startR |2.2.1 | | | | -|steps |1.3.0 | | | | -|supercells |0.9.1 | | | | -|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | -|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | -|tarchetypes |0.7.4 | | | | -|[targeted](problems.md#targeted)|0.3 | | |1 | -|targets |0.14.2 | | | | -|tcplfit2 |0.1.3 | | | | -|tealeaves |1.0.6 | | | | -|templr |0.2-0 | | | | -|[text](problems.md#text) |0.9.99.2 | | |1 | -|tglkmeans |0.3.5 | | | | -|tidyqwi |0.1.2 | | | | -|TKCat |1.0.7 | | | | -|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | -|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | -|tsfeatures |1.1 | | | | -|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | -|[txshift](problems.md#txshift)|0.3.8 | | |1 | -|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.9 | | |1 | -|[updog](problems.md#updog)|2.1.3 | | |1 | -|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | -|webdeveloper |1.0.5 | | | | -|whitewater |0.1.2 | | | | -|wildmeta |0.3.1 | | | | -|[wru](problems.md#wru) |1.0.1 | | |2 | -|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | -|yfR |1.1.0 | | | | +|package |version |error |warning |note | +|:------------------------|:---------|:--------|:-------|:----| +|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | +|alookr |0.3.7 | | | | +|alphaci |1.0.0 | | | | +|AlpsNMR |4.0.4 | | | | +|arkdb |0.0.16 | | | | +|aroma.affymetrix |3.2.1 | | | | +|aroma.cn |1.7.0 | | | | +|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | +|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | +|bamm |0.4.3 | | | | +|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | +|BatchGetSymbols |2.6.4 | | | | +|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | +|bayesian |0.0.9 | | | | +|bayesmove |0.2.1 | | | | +|bcmaps |1.1.0 | | | | +|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | +|bhmbasket |0.9.5 | | | | +|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | +|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | +|bkmrhat |1.1.3 | | | | +|[blavaan](problems.md#blavaan)|0.4-6 | | |3 | +|bolasso |0.2.0 | | | | +|[brms](problems.md#brms) |2.18.0 | | |2 | +|brpop |0.1.5 | | | | +|canaper |1.0.0 | | | | +|ceRNAnetsim |1.10.0 | | | | +|cft |1.0.0 | | | | +|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | +|[civis](problems.md#civis)|3.1.0 |__+1__ | | | +|Clustering |1.7.7 | | | | +|codalm |0.1.2 | | | | +|[codebook](problems.md#codebook)|0.9.2 | | |3 | +|conformalInference.fd |1.1.1 | | | | +|conformalInference.multi |1.1.1 | | | | +|crossmap |0.4.0 | | | | +|CSCNet |0.1.2 | | | | +|[cSEM](problems.md#csem) |0.5.0 | | |1 | +|[CSGo](problems.md#csgo) |0.6.7 | | |1 | +|cvCovEst |1.2.0 | | | | +|dagHMM |0.1.0 | | | | +|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | +|delayed |0.4.0 | | | | +|dhReg |0.1.1 | | | | +|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | +|disk.frame |0.8.0 | | | | +|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | +|doFuture |0.12.2 | | | | +|DQAstats |0.3.2 | | | | +|[dragon](problems.md#dragon)|1.2.1 | | |1 | +|drake |7.13.4 | | | | +|drimmR |1.0.1 | | | | +|drtmle |1.1.2 | | | | +|dsos |0.1.2 | | | | +|DT |0.27 | | | | +|easyalluvial |0.3.1 | | | | +|ecic |0.0.3 | | | | +|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | +|elevatr |0.4.2 | | | | +|[envi](problems.md#envi) |0.1.17 | |1 | | +|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | +|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | +|epwshiftr |0.1.3 | | | | +|ezcox |1.0.2 | | | | +|fabletools |0.3.2 | | | | +|FAMoS |0.3.0 | | | | +|fastRhockey |0.4.0 | | | | +|[fect](problems.md#fect) |1.0.0 | | |2 | +|fiery |1.1.4 | | | | +|finbif |0.7.2 | | | | +|fitlandr |0.1.0 | | | | +|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | +|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | +|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | +|fst4pg |1.0.0 | | | | +|fundiversity |1.1.1 | | | | +|funGp |0.3.1 | | | | +|furrr |0.3.1 | | | | +|future.apply |1.10.0 | | | | +|future.batchtools |0.12.0 | | | | +|future.callr |0.8.1 | | | | +|future.tests |0.5.0 | | | | +|fxTWAPLS |0.1.2 | | | | +|genBaRcode |1.2.5 | | | | +|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | +|GetBCBData |0.7.0 | | | | +|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | +|googlePubsubR |0.0.3 | | | | +|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | +|[greed](problems.md#greed)|0.6.1 | | |2 | +|greta |0.4.3 | | | | +|gstat |2.1-0 | | | | +|GSVA |1.46.0 | | | | +|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | +|gtfs2emis |0.1.0 | | | | +|gtfs2gps |2.1-0 | | | | +|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | +|hacksig |0.1.2 | | | | +|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | +|haldensify |0.2.3 | | | | +|hoopR |1.8.0 | | | | +|[hwep](problems.md#hwep) |2.0.0 | | |2 | +|idmodelr |0.4.0 | | | | +|imagefluency |0.2.4 | | | | +|iml |0.11.1 | | | | +|incubate |1.2.0 | | | | +|[infercnv](problems.md#infercnv)|1.14.0 | | |2 | +|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | +|[InPAS](problems.md#inpas)|2.6.0 | | |1 | +|[interflex](problems.md#interflex)|1.2.6 | | |1 | +|ipc |0.1.4 | | | | +|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | +|isopam |1.1.0 | | | | +|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | +|JointAI |1.0.4 | | | | +|jstor |0.3.10 | | | | +|JuliaConnectoR |1.1.1 | | | | +|kernelboot |0.1.9 | | | | +|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | +|latentcor |2.0.1 | | | | +|lava |1.7.2.1 | | | | +|ldaPrototype |0.3.1 | | | | +|ldsr |0.0.2 | | | | +|lemna |1.0.0 | | | | +|LexFindR |1.0.2 | | | | +|lgr |0.4.4 | | | | +|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | +|[lightr](problems.md#lightr)|1.7.0 | | |2 | +|lmtp |1.3.1 | | | | +|LWFBrook90R |0.5.2 | | | | +|[MAI](problems.md#mai) |1.4.0 | | |1 | +|MAMS |2.0.0 | | | | +|marginaleffects |0.10.0 | | | | +|mcmcensemble |3.0.0 | | | | +|mcp |0.3.2 | | | | +|merTools |0.5.2 | | | | +|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | +|[mice](problems.md#mice) |3.15.0 | |1 | | +|[microservices](problems.md#microservices)|0.2.0 |1 | | | +|microSTASIS |0.1.0 | | | | +|migraph |0.13.2 | | | | +|mikropml |1.5.0 | | | | +|[MineICA](problems.md#mineica)|1.38.0 |1 __+1__ |3 |4 | +|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | +|[mistyR](problems.md#mistyr)|1.6.1 | | |1 | +|mlr3 |0.14.1 | | | | +|mlr3db |0.5.0 | | | | +|mlr3pipelines |0.4.2 | | | | +|mlr3spatial |0.3.1 | | | | +|modelsummary |1.3.0 | | | | +|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | +|MOSS |0.2.2 | | | | +|mrgsim.parallel |0.2.1 | | | | +|[mslp](problems.md#mslp) |1.0.1 |1 | | | +|multiverse |0.6.1 | | | | +|netShiny |1.0 | | | | +|NetSimR |0.1.2 | | | | +|nfl4th |1.0.2 | | | | +|nflfastR |4.5.1 | | | | +|nflseedR |1.2.0 | | | | +|nncc |1.0.0 | | | | +|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | +|onemapsgapi |1.1.0 | | | | +|[OOS](problems.md#oos) |1.0.0 | | |1 | +|origami |1.0.7 | | | | +|paramsim |0.1.0 | | | | +|[partR2](problems.md#partr2)|0.9.1 | | |1 | +|[pavo](problems.md#pavo) |2.8.0 | |1 | | +|pbapply |1.7-0 | | | | +|PCRedux |1.1-2 | | | | +|PeakSegDisk |2022.2.1 | | | | +|penaltyLearning |2020.5.13 | | | | +|pGRN |0.3.5 | | | | +|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | +|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | +|PINstimation |0.1.1 | | | | +|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | +|plumber |1.2.1 | | | | +|polle |1.2 | | | | +|POMADE |0.1.0 | | | | +|[portvine](problems.md#portvine)|1.0.2 | | |1 | +|powRICLPM |0.1.1 | | | | +|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | +|[prewas](problems.md#prewas)|1.1.1 | | |1 | +|progressr |0.13.0 | | | | +|[projpred](problems.md#projpred)|2.4.0 | | |1 | +|[promises](problems.md#promises)|1.2.0.1 | | |1 | +|Prostar |1.30.7 | | | | +|protti |0.6.0 | | | | +|PSCBS |0.66.0 | | | | +|PUMP |1.0.1 | | | | +|qape |2.0 | | | | +|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | +|qgcomp |2.10.1 | | | | +|qgcompint |0.7.0 | | | | +|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | +|rangeMapper |2.0.3 | | | | +|rBiasCorrection |0.3.4 | | | | +|receptiviti |0.1.3 | | | | +|refineR |1.5.1 | | | | +|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | +|remiod |1.0.2 | | | | +|reproducible |1.2.16 | | | | +|reval |3.1-0 | | | | +|[rgee](problems.md#rgee) |1.1.5 | | |2 | +|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | +|robust2sls |0.2.2 | | | | +|RTransferEntropy |0.2.21 | | | | +|s3fs |0.1.2 | | | | +|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | +|scBubbletree |1.0.0 | | | | +|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | +|SCtools |0.3.2.1 | | | | +|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | +|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | +|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | +|seer |1.1.8 | | | | +|semtree |0.9.18 | | | | +|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[Seurat](problems.md#seurat)|4.3.0 | | |2 | +|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | +|[shiny](problems.md#shiny)|1.7.4 | | |1 | +|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | +|sigminer |2.1.9 | | | | +|Signac |1.9.0 | | | | +|[signeR](problems.md#signer)|2.0.2 | | |3 | +|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | +|simfinapi |0.2.0 | | | | +|simglm |0.8.9 | | | | +|simhelpers |0.1.2 | | | | +|sims |0.0.3 | | | | +|skewlmm |1.0.0 | | | | +|[skpr](problems.md#skpr) |1.1.6 | | |1 | +|smoots |1.1.3 | | | | +|sNPLS |1.0.27 | | | | +|[solitude](problems.md#solitude)|1.1.3 | | |1 | +|sovereign |1.2.1 | | | | +|[spaMM](problems.md#spamm)|4.1.20 | | |2 | +|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | +|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | +|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | +|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | +|specr |1.0.0 | | | | +|sperrorest |3.0.5 | | | | +|spFSR |2.0.3 | | | | +|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | +|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | +|[squat](problems.md#squat)|0.1.0 | | |1 | +|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | +|[stars](problems.md#stars)|0.6-0 | | |2 | +|startR |2.2.1 | | | | +|steps |1.3.0 | | | | +|supercells |0.9.1 | | | | +|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | +|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | +|tarchetypes |0.7.4 | | | | +|[targeted](problems.md#targeted)|0.3 | | |1 | +|targets |0.14.2 | | | | +|tcplfit2 |0.1.3 | | | | +|tealeaves |1.0.6 | | | | +|templr |0.2-0 | | | | +|[text](problems.md#text) |0.9.99.2 | | |1 | +|tglkmeans |0.3.5 | | | | +|tidyqwi |0.1.2 | | | | +|TKCat |1.0.7 | | | | +|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | +|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | +|tsfeatures |1.1 | | | | +|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | +|[txshift](problems.md#txshift)|0.3.8 | | |1 | +|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.9 | | |1 | +|[updog](problems.md#updog)|2.1.3 | | |1 | +|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | +|webdeveloper |1.0.5 | | | | +|whitewater |0.1.2 | | | | +|wildmeta |0.3.1 | | | | +|[wru](problems.md#wru) |1.0.1 | | |2 | +|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | +|yfR |1.1.0 | | | | diff --git a/revdep/problems.md b/revdep/problems.md index 8d97d0ad..a9d81093 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -98,7 +98,7 @@ Run `revdep_details(, "baseballr")` for more info ... Quitting from lines 38-40 (using_statcast_pitch_data.Rmd) Error: processing vignette 'using_statcast_pitch_data.Rmd' failed with diagnostics: - HTTP error 404. + Timeout was reached: [] Operation timed out after 10001 milliseconds with 0 out of 0 bytes received --- failed re-building ‘using_statcast_pitch_data.Rmd’ SUMMARY: processing the following file failed: @@ -1288,7 +1288,7 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 238761 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 117874 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 ERROR Running the tests in ‘tests/testthat.R’ failed. @@ -1465,8 +1465,54 @@ Run `revdep_details(, "MineICA")` for more info
+## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘MineICA-Ex.R’ failed + The error most likely occurred in: + + > ### Name: IcaSet + > ### Title: Class to Contain and Describe an ICA decomposition of + > ### High-Throughput Data. + > ### Aliases: class:IcaSet IcaSet IcaSet-class [ [,ANY,ANY,IcaSet-method + > ### [,IcaSet,ANY-method [,IcaSet,ANY,ANY-method + > ### [,IcaSet,ANY,ANY,ANY-method [<- [<-,IcaSet,ANY,ANY,ANY,ANY-method + > ### [<-,IcaSet,ANY,ANY,ANY-method [<-,IcaSet,ANY,ANY-method organism + ... + > ### Keywords: classes + > + > ### ** Examples + > + > # create an instance of IcaSet + > new("IcaSet") + Error in curl::curl_fetch_memory(url, handle = handle) : + Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 0 out of -1 bytes received + Calls: new ... request_fetch -> request_fetch.write_memory -> + Execution halted + ``` + ## In both +* checking running R code from vignettes ... + ``` + ‘MineICA.Rnw’... failed + ERROR + Errors in running code in vignettes: + when running code in ‘MineICA.Rnw’ + ... + > resPath(params) + [1] "mainz/" + + > resW <- writeProjByComp(icaSet = icaSetMainz, params = params, + + mart = mart, level = "genes", selCutoffWrite = 2.5) + + When sourcing ‘MineICA.R’: + Error: task 2 failed - "Multiple cache results found. + Please clear your cache by running biomartCacheClear()" + Execution halted + ``` + * checking dependencies in R code ... WARNING ``` Namespace in Imports field not imported from: ‘lumiHumanAll.db’ @@ -1575,8 +1621,8 @@ Run `revdep_details(, "MineICA")` for more info IQR, mad, sd, var, xtabs ... - Error in { : task 2 failed - "Multiple cache results found. - Please clear your cache by running biomartCacheClear()" + Error in curl::curl_fetch_memory(url, handle = handle) : + Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 108580 out of -1 bytes received --- failed re-building ‘MineICA.Rnw’ @@ -1726,10 +1772,10 @@ Run `revdep_details(, "oncomsm")` for more info * checking installed package size ... NOTE ``` - installed size is 55.3Mb + installed size is 55.6Mb sub-directories of 1Mb or more: doc 1.3Mb - libs 53.0Mb + libs 53.2Mb ``` * checking for GNU extensions in Makefiles ... NOTE From dce18390461fae6c9a2792fad95b72abe29756d1 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 28 Feb 2023 14:19:25 +0100 Subject: [PATCH 76/88] Journals: rename 'type' to 'category' --- DESCRIPTION | 2 +- R/ClusterFuture-class.R | 50 ++++++++++++++++++------------------- R/Future-class.R | 16 ++++++------ R/MulticoreFuture-class.R | 10 ++++---- R/future.R | 2 +- R/journal.R | 52 +++++++++++++++++++++------------------ R/options.R | 5 ++++ R/resolve.R | 2 +- R/resolved.R | 2 +- man/future.options.Rd | 2 ++ 10 files changed, 77 insertions(+), 66 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index b1bdf3a5..3470fada 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9112 +Version: 1.31.0-9113 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/ClusterFuture-class.R b/R/ClusterFuture-class.R index 18dac0e0..0af79050 100644 --- a/R/ClusterFuture-class.R +++ b/R/ClusterFuture-class.R @@ -121,11 +121,11 @@ run.ClusterFuture <- function(future, ...) { if (inherits(future$.journal, "FutureJournal")) { appendToFutureJournal(future, - event = "getWorker", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() + event = "getWorker", + category = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) } @@ -139,11 +139,11 @@ run.ClusterFuture <- function(future, ...) { cluster_call(cl, fun = grmall, future = future, when = "call grmall() on") if (inherits(future$.journal, "FutureJournal")) { appendToFutureJournal(future, - event = "eraseWorker", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() + event = "eraseWorker", + category = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) } } @@ -167,11 +167,11 @@ run.ClusterFuture <- function(future, ...) { if (inherits(future$.journal, "FutureJournal")) { appendToFutureJournal(future, - event = "attachPackages", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() + event = "attachPackages", + category = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) } @@ -204,11 +204,11 @@ run.ClusterFuture <- function(future, ...) { if (inherits(future$.journal, "FutureJournal")) { appendToFutureJournal(future, - event = "exportGlobals", - type = "overhead", - parent = "launch", - start = t_start, - stop = Sys.time() + event = "exportGlobals", + category = "overhead", + parent = "launch", + start = t_start, + stop = Sys.time() ) } } @@ -445,11 +445,11 @@ receiveMessageFromWorker <- function(future, ...) { if (inherits(future$.journal, "FutureJournal")) { appendToFutureJournal(future, - event = "receiveResult", - type = "overhead", - parent = "gather", - start = t_start, - stop = Sys.time() + event = "receiveResult", + category = "overhead", + parent = "gather", + start = t_start, + stop = Sys.time() ) } diff --git a/R/Future-class.R b/R/Future-class.R index b5082ba8..8c5c649b 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -468,10 +468,10 @@ run <- function(future, ...) { start <- Sys.time() on.exit({ appendToFutureJournal(future, - event = "launch", - type = "overhead", - start = start, - stop = Sys.time() + event = "launch", + category = "overhead", + start = start, + stop = Sys.time() ) }) } @@ -488,10 +488,10 @@ result <- function(future, ...) { start <- Sys.time() on.exit({ appendToFutureJournal(future, - event = "gather", - type = "overhead", - start = start, - stop = Sys.time() + event = "gather", + category = "overhead", + start = start, + stop = Sys.time() ) ## Signal FutureJournalCondition? diff --git a/R/MulticoreFuture-class.R b/R/MulticoreFuture-class.R index 9b119cd3..bfbb38c2 100644 --- a/R/MulticoreFuture-class.R +++ b/R/MulticoreFuture-class.R @@ -68,11 +68,11 @@ run.MulticoreFuture <- function(future, ...) { if (inherits(future$.journal, "FutureJournal")) { appendToFutureJournal(future, - event = "getWorker", - type = "other", - parent = "launch", - start = t_start, - stop = Sys.time() + event = "getWorker", + category = "other", + parent = "launch", + start = t_start, + stop = Sys.time() ) } diff --git a/R/future.R b/R/future.R index 6fa90e72..f94451d3 100644 --- a/R/future.R +++ b/R/future.R @@ -219,7 +219,7 @@ future <- function(expr, envir = parent.frame(), substitute = TRUE, lazy = FALSE ## Enable journaling? if (getOption("future.journal", FALSE)) { - future <- makeFutureJournal(future, event = "create", type = "overhead", start = t_start) + future <- makeFutureJournal(future, event = "create", category = "overhead", start = t_start) } if (!lazy) { diff --git a/R/journal.R b/R/journal.R index 792778b2..e524cf99 100644 --- a/R/journal.R +++ b/R/journal.R @@ -14,38 +14,42 @@ #' @return #' A data frame of class `FutureJournal` with columns: #' -#' 1. `event` (character string) -#' 2. `type` (character string) -#' 3. `parent` (character string) -#' 4. `start` (POSIXct) -#' 5. `at` (difftime) -#' 6. `duration` (difftime) -#' 7. `future_label` (character string) -#' 8. `future_uuid` (character string) -#' 9. `session_uuid` (character string) +#' 1. `event` (character string) - type of event that took place +#' 2. `category` (character string) - the category of the event +#' 3. `parent` (character string) - (to be describe) +#' 4. `start` (POSIXct) - the timestamp when the event started +#' 5. `at` (difftime) - the time when the event started relative to +#' first event +#' 6. `duration` (difftime) - the duration of the event +#' 7. `future_label` (character string) - the label of the future +#' 8. `future_uuid` (character string) - the UUID of the future +#' 9. `session_uuid` (character string) - the UUID of the R session +#' where the event took place #' -#' Common events are: +#' The common events are: #' #' * `create` - the future was created (an `overhead`) #' * `launch` - the future was launched (an `overhead`) #' * `evaluate` - the future was evaluated (an `evaluation`) -#' * `resolved` - the future was queried (may be occur multiple times) (an `overhead`) +#' * `resolved` - the future was queried (may be occur multiple times) +#' (an `overhead`) #' * `gather` - the results was retrieved (an `overhead`) #' #' but others may be added by other Future classes. #' -#' Common event types are: +#' Common event categorys are: #' #' * `evaluation` - processing time is spent on evaluation #' * `overhead` - processing time is spent on orchestrating the future -#' * `waiting` - processing time is spent on waiting to set up or querying the future +#' * `waiting` - processing time is spent on waiting to set up or +#' querying the future #' #' but others may be added by other Future classes. #' #' The data frame is sorted by the `at` time. #' Note that the timestamps for the `evaluate` event are based on the local #' time on the worker. The system clocks on the worker and the calling R -#' system may be out of sync. +#' system may not be in perfect sync. #' #' @section Enabling and disabling event logging: #' To enable logging of events, set option `future.journal` is TRUE. @@ -79,7 +83,7 @@ journal.Future <- function(x, ...) { stop_if_not(is.character(session_uuid)) x <- appendToFutureJournal(x, event = "evaluate", - type = "evaluation", + category = "evaluation", start = x$result$started, stop = x$result$finished ) @@ -161,7 +165,7 @@ print.FutureJournal <- function(x, digits.secs = 3L, ...) { #' @export summary.FutureJournal <- function(object, ...) { ## To please 'R CMD check' - event <- future_uuid <- median <- parent <- type <- NULL + event <- future_uuid <- median <- parent <- category <- NULL dt_top <- subset(object, is.na(parent)) @@ -204,8 +208,8 @@ summary.FutureJournal <- function(object, ...) { uuid <- uuids[[kk]] dt_uuid <- subset(dt_top, future_uuid == uuid) res <- data.frame( - evaluate = subset(dt_uuid, type == "evaluation")[["duration"]], - overhead = sum(subset(dt_uuid, type == "overhead")[["duration"]]) + evaluate = subset(dt_uuid, category == "evaluation")[["duration"]], + overhead = sum(subset(dt_uuid, category == "overhead")[["duration"]]) ) res[["duration"]] <- t_delta[kk] eff[[uuid]] <- res @@ -254,18 +258,18 @@ print.FutureJournalSummary <- function(x, ...) { } -makeFutureJournal <- function(x, event = "create", type = "other", parent = NA_character_, start = stop, stop = Sys.time()) { +makeFutureJournal <- function(x, event = "create", category = "other", parent = NA_character_, start = stop, stop = Sys.time()) { stop_if_not( inherits(x, "Future"), is.null(x$.journal), length(event) == 1L, is.character(event), !is.na(event), - length(type) == 1L, is.character(type), !is.na(event), + length(category) == 1L, is.character(category), !is.na(event), length(parent) == 1L, is.character(parent), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(event = event, type = type, parent = parent, start = start, stop = stop) + data <- data.frame(event = event, category = category, parent = parent, start = start, stop = stop) class(data) <- c("FutureJournal", class(data)) x$.journal <- data invisible(x) @@ -298,7 +302,7 @@ updateFutureJournal <- function(x, event, start = NULL, stop = Sys.time()) { } -appendToFutureJournal <- function(x, event, type = "other", parent = NA_character_, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { +appendToFutureJournal <- function(x, event, category = "other", parent = NA_character_, start = Sys.time(), stop = as.POSIXct(NA_real_), skip = TRUE) { ## Nothing to do? if (!inherits(x$.journal, "FutureJournal")) return(x) @@ -307,13 +311,13 @@ appendToFutureJournal <- function(x, event, type = "other", parent = NA_characte stop_if_not( inherits(x, "Future"), length(event) == 1L, is.character(event), !is.na(event), - length(type) == 1L, is.character(type), !is.na(event), + length(category) == 1L, is.character(category), !is.na(event), length(parent) == 1L, is.character(parent), length(start) == 1L, inherits(start, "POSIXct"), length(stop) == 1L, inherits(stop, "POSIXct") ) - data <- data.frame(event = event, type = type, parent = parent, start = start, stop = stop) + data <- data.frame(event = event, category = category, parent = parent, start = start, stop = stop) x$.journal <- rbind(x$.journal, data) invisible(x) } diff --git a/R/options.R b/R/options.R index 4f96ba9f..393f08dc 100644 --- a/R/options.R +++ b/R/options.R @@ -171,6 +171,8 @@ #' R_FUTURE_RESOLVED_TIMEOUT #' future.output.windows.reencode #' R_FUTURE_OUTPUT_WINDOWS_REENCODE +#' future.journal +#' R_FUTURE_JOURNAL #' #' @name future.options NULL @@ -333,4 +335,7 @@ update_package_options <- function(debug = FALSE) { ## future 1.32.0: update_package_option("future.state.onInvalid", mode = "character", debug = debug) + + ## future 1.32.0: + update_package_option("future.journal", mode = "logical", debug = debug) } diff --git a/R/resolve.R b/R/resolve.R index 47f0fa5f..f70a6996 100644 --- a/R/resolve.R +++ b/R/resolve.R @@ -61,7 +61,7 @@ resolve.Future <- function(x, idxs = NULL, recursive = 0, result = FALSE, stdout on.exit({ appendToFutureJournal(x, event = "resolve", - type = "overhead", + category = "overhead", start = t_start, stop = Sys.time(), skip = FALSE diff --git a/R/resolved.R b/R/resolved.R index 89129528..f438d514 100644 --- a/R/resolved.R +++ b/R/resolved.R @@ -27,7 +27,7 @@ resolved <- function(x, ...) { on.exit({ appendToFutureJournal(x, event = "resolved", - type = "querying", + category = "querying", start = start, stop = Sys.time(), skip = FALSE diff --git a/man/future.options.Rd b/man/future.options.Rd index 1cafcdbc..8c17a2c1 100644 --- a/man/future.options.Rd +++ b/man/future.options.Rd @@ -43,6 +43,8 @@ \alias{R_FUTURE_RESOLVED_TIMEOUT} \alias{future.output.windows.reencode} \alias{R_FUTURE_OUTPUT_WINDOWS_REENCODE} +\alias{future.journal} +\alias{R_FUTURE_JOURNAL} \title{Options used for futures} \description{ Below are the \R options and environment variables that are used by the From 26685b7f96b4070c39ea09239360920dd5e776ba Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 28 Feb 2023 14:43:11 +0100 Subject: [PATCH 77/88] GHA: fix R (< 3.5.0) checks --- .github/workflows/R-CMD-check.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index e4af93e1..a86aefa3 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -103,6 +103,7 @@ jobs: run: | if (nzchar(Sys.getenv("R_FUTURE_PLAN")) || getRversion() < "3.5.0") Sys.setenv(RCMDCHECK_ERROR_ON = "error") rcmdcheck::rcmdcheck( + build_args = if (getRversion() < "3.5.0") "--no-build-vignettes", args = c("--no-manual", "--as-cran", if (getRversion() < "3.5.0") c("--no-vignettes", "--no-build-vignettes", "--ignore-vignettes")), check_dir = "check" ) @@ -112,7 +113,6 @@ jobs: if: runner.os == 'Windows' run: | rcmdcheck::rcmdcheck( - build_args = if (getRversion() < "3.5.0") "--no-build-vignettes", args = c("--no-manual", "--as-cran", if (.Platform$OS.type == "windows" && getRversion() >= "4.2.0") "--no-multiarch"), check_dir = "check" ) From c8443b6482ff6b3e2bf0db5a80545d46c4bcf4d5 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Mar 2023 13:46:34 +0100 Subject: [PATCH 78/88] README: don't mention deprecated 'multiprocess' + guess-edit README_ja.md --- README.md | 2 -- README_ja.md | 20 +------------------- 2 files changed, 1 insertion(+), 21 deletions(-) diff --git a/README.md b/README.md index daf0d607..58fe9f2c 100644 --- a/README.md +++ b/README.md @@ -104,8 +104,6 @@ The future package implements the following types of futures: | `multicore` | not Windows/not RStudio | forked R processes (on current machine) | `cluster` | all | external R sessions on current, local, and/or remote machines -_Comment:_ The alias strategy `multiprocess` was deprecated in future (>= 1.20.0) in favor of `multisession` and `multicore`. - The future package is designed such that support for additional strategies can be implemented as well. For instance, the [future.callr] package provides future backends that evaluates futures in a background R process utilizing the [callr] package - they work similarly to `multisession` futures but has a few advantages. Continuing, the [future.batchtools] package provides futures for all types of _cluster functions_ ("backends") that the [batchtools] package supports. Specifically, futures for evaluating R expressions via job schedulers such as Slurm, TORQUE/PBS, Oracle/Sun Grid Engine (SGE) and Load Sharing Facility (LSF) are also available. By default, future expressions are evaluated eagerly (= instantaneously) and synchronously (in the current R session). This evaluation strategy is referred to as "sequential". In this section, we will go through each of these strategies and discuss what they have in common and how they differ. diff --git a/README_ja.md b/README_ja.md index 34c06ccf..29fadc51 100644 --- a/README_ja.md +++ b/README_ja.md @@ -225,12 +225,6 @@ cluster all external R sessions on current, local, and/or remote machines | `multicore` | Windows以外/RStudio以外 | フォークされた R プロセス(現行のマシン上) | | `cluster` | すべて | 外部 R セッション(現行、ローカル、リモートマシン上) | - - -**注意:** future (>= 1.20.0) では、`multiprocess` は非推奨となり、`multisession` または `multicore` の明確な指定が推奨される。 - 同期的フューチャはフューチャを作成した R プロセスで一つひとつ解決される。 同期的フューチャが解決されている間、メインプロセスはブロックされる。 -future パッケージの同期的フューチャには2つの種類がある。 **逐次的フューチャ**と**透過的フューチャ**である。 + #### 逐次的フューチャ (Sequential Future) @@ -409,17 +402,6 @@ ID が代入されている)は上書きも削除もされないことに注 同期的な(単一の)プロセスが評価に使われるので、フューチャ `b` はメインの R プロセスによって(ローカル環境で)解決される 。 これが `b` の値と `pid` が一致する理由である。 -#### 透過的フューチャ (Transparent Future) - - - -透過的フューチャは `plan(transparent)` を指定することで利用できる。 -このフューチャは、評価時にエラーや警告などの通知を即時的に行う逐次的フューチャであり、代入は呼び出し環境で行われる。 -透過的フューチャは他の戦略では絞り込むことが難しいエラーのトラブルシューティングに役立つ。 ### 非同期的フューチャ From dfbb33b89b1429c24075723ed9a9eda3d4aca8c3 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Wed, 1 Mar 2023 23:18:02 +0100 Subject: [PATCH 79/88] CLEANUP: From workarounds for the 'civis' package; no longer needed --- DESCRIPTION | 2 +- R/Future-class.R | 10 ---------- R/signalConditions.R | 3 +-- 3 files changed, 2 insertions(+), 13 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 3470fada..7dd0e5a2 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9113 +Version: 1.31.0-9114 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/R/Future-class.R b/R/Future-class.R index 8c5c649b..479eb5ce 100644 --- a/R/Future-class.R +++ b/R/Future-class.R @@ -864,16 +864,6 @@ packages.Future <- function(future, ...) { if (!is.element(value, c("created", "running", "finished", "failed", "interrupted"))) { action <- getOption("future.state.onInvalid", "warning") - ## FIXME: civis::CivisFuture uses 'succeeded' /HB 2019-06-18 - if (Sys.getenv("R_FUTURE_CHECK_IGNORE_CIVIS", "true") == "true") { - for (call in sys.calls()) { - if (any(grepl("CivisFuture$", as.character(call[[1]])))) { - action <- "ignore" - break - } - } - } - if (action != "ignore") { msg <- sprintf("Trying to assign an invalid value to the internal '%s' field of a %s object: %s", name, class(x)[1], value) if (action == "error") { diff --git a/R/signalConditions.R b/R/signalConditions.R index c0acfa66..1bc2f07d 100644 --- a/R/signalConditions.R +++ b/R/signalConditions.R @@ -26,8 +26,7 @@ #' @keywords internal signalConditions <- function(future, include = "condition", exclude = NULL, resignal = TRUE, ...) { ## Future is not yet launched - ## FIXME: civis::CivisFuture uses 'succeeded' /HB 2019-06-18 - if (!future$state %in% c("finished", "failed", "succeeded")) { + if (!future$state %in% c("finished", "failed")) { stop(FutureError( sprintf( "Internal error: Cannot resignal future conditions. %s has not yet been resolved (state = %s)", From b0379fd3e816ccfe29311d032eda71e4ca26eeca Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Thu, 2 Mar 2023 14:26:23 -0800 Subject: [PATCH 80/88] REVDEP: 280 revdep packages [ci skip] --- revdep/README.md | 575 ++++++++++++++++++++++----------------------- revdep/cran.md | 10 +- revdep/problems.md | 179 +++++++------- 3 files changed, 379 insertions(+), 385 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index c584d773..99c92408 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,14 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-02-27 | +|date |2023-03-02 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies |package |old |new |Δ | |:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9112 |* | +|future |1.31.0 |1.31.0-9114 |* | |codetools |0.2-19 |0.2-19 | | |digest |0.6.31 |0.6.31 | | |globals |0.16.2 |0.16.2 | | @@ -26,295 +26,288 @@ # Revdeps -## New problems (2) - -|package |version |error |warning |note | -|:-------|:-------|:--------|:-------|:----| -|[civis](problems.md#civis)|3.1.0 |__+1__ | | | -|[MineICA](problems.md#mineica)|1.38.0 |1 __+1__ |3 |4 | - ## All (280) -|package |version |error |warning |note | -|:------------------------|:---------|:--------|:-------|:----| -|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | -|alookr |0.3.7 | | | | -|alphaci |1.0.0 | | | | -|AlpsNMR |4.0.4 | | | | -|arkdb |0.0.16 | | | | -|aroma.affymetrix |3.2.1 | | | | -|aroma.cn |1.7.0 | | | | -|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | -|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | -|bamm |0.4.3 | | | | -|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | -|BatchGetSymbols |2.6.4 | | | | -|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | -|bayesian |0.0.9 | | | | -|bayesmove |0.2.1 | | | | -|bcmaps |1.1.0 | | | | -|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | -|bhmbasket |0.9.5 | | | | -|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | -|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | -|bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan)|0.4-6 | | |3 | -|bolasso |0.2.0 | | | | -|[brms](problems.md#brms) |2.18.0 | | |2 | -|brpop |0.1.5 | | | | -|canaper |1.0.0 | | | | -|ceRNAnetsim |1.10.0 | | | | -|cft |1.0.0 | | | | -|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | -|[civis](problems.md#civis)|3.1.0 |__+1__ | | | -|Clustering |1.7.7 | | | | -|codalm |0.1.2 | | | | -|[codebook](problems.md#codebook)|0.9.2 | | |3 | -|conformalInference.fd |1.1.1 | | | | -|conformalInference.multi |1.1.1 | | | | -|crossmap |0.4.0 | | | | -|CSCNet |0.1.2 | | | | -|[cSEM](problems.md#csem) |0.5.0 | | |1 | -|[CSGo](problems.md#csgo) |0.6.7 | | |1 | -|cvCovEst |1.2.0 | | | | -|dagHMM |0.1.0 | | | | -|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | -|delayed |0.4.0 | | | | -|dhReg |0.1.1 | | | | -|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | -|disk.frame |0.8.0 | | | | -|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | -|doFuture |0.12.2 | | | | -|DQAstats |0.3.2 | | | | -|[dragon](problems.md#dragon)|1.2.1 | | |1 | -|drake |7.13.4 | | | | -|drimmR |1.0.1 | | | | -|drtmle |1.1.2 | | | | -|dsos |0.1.2 | | | | -|DT |0.27 | | | | -|easyalluvial |0.3.1 | | | | -|ecic |0.0.3 | | | | -|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | -|elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.17 | |1 | | -|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | -|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | -|epwshiftr |0.1.3 | | | | -|ezcox |1.0.2 | | | | -|fabletools |0.3.2 | | | | -|FAMoS |0.3.0 | | | | -|fastRhockey |0.4.0 | | | | -|[fect](problems.md#fect) |1.0.0 | | |2 | -|fiery |1.1.4 | | | | -|finbif |0.7.2 | | | | -|fitlandr |0.1.0 | | | | -|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | -|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | -|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | -|fst4pg |1.0.0 | | | | -|fundiversity |1.1.1 | | | | -|funGp |0.3.1 | | | | -|furrr |0.3.1 | | | | -|future.apply |1.10.0 | | | | -|future.batchtools |0.12.0 | | | | -|future.callr |0.8.1 | | | | -|future.tests |0.5.0 | | | | -|fxTWAPLS |0.1.2 | | | | -|genBaRcode |1.2.5 | | | | -|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | -|GetBCBData |0.7.0 | | | | -|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | -|googlePubsubR |0.0.3 | | | | -|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | -|[greed](problems.md#greed)|0.6.1 | | |2 | -|greta |0.4.3 | | | | -|gstat |2.1-0 | | | | -|GSVA |1.46.0 | | | | -|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | -|gtfs2emis |0.1.0 | | | | -|gtfs2gps |2.1-0 | | | | -|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | -|hacksig |0.1.2 | | | | -|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | -|haldensify |0.2.3 | | | | -|hoopR |1.8.0 | | | | -|[hwep](problems.md#hwep) |2.0.0 | | |2 | -|idmodelr |0.4.0 | | | | -|imagefluency |0.2.4 | | | | -|iml |0.11.1 | | | | -|incubate |1.2.0 | | | | -|[infercnv](problems.md#infercnv)|1.14.0 | | |2 | -|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | -|[InPAS](problems.md#inpas)|2.6.0 | | |1 | -|[interflex](problems.md#interflex)|1.2.6 | | |1 | -|ipc |0.1.4 | | | | -|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | -|isopam |1.1.0 | | | | -|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | -|JointAI |1.0.4 | | | | -|jstor |0.3.10 | | | | -|JuliaConnectoR |1.1.1 | | | | -|kernelboot |0.1.9 | | | | -|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | -|latentcor |2.0.1 | | | | -|lava |1.7.2.1 | | | | -|ldaPrototype |0.3.1 | | | | -|ldsr |0.0.2 | | | | -|lemna |1.0.0 | | | | -|LexFindR |1.0.2 | | | | -|lgr |0.4.4 | | | | -|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | -|[lightr](problems.md#lightr)|1.7.0 | | |2 | -|lmtp |1.3.1 | | | | -|LWFBrook90R |0.5.2 | | | | -|[MAI](problems.md#mai) |1.4.0 | | |1 | -|MAMS |2.0.0 | | | | -|marginaleffects |0.10.0 | | | | -|mcmcensemble |3.0.0 | | | | -|mcp |0.3.2 | | | | -|merTools |0.5.2 | | | | -|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | -|[mice](problems.md#mice) |3.15.0 | |1 | | -|[microservices](problems.md#microservices)|0.2.0 |1 | | | -|microSTASIS |0.1.0 | | | | -|migraph |0.13.2 | | | | -|mikropml |1.5.0 | | | | -|[MineICA](problems.md#mineica)|1.38.0 |1 __+1__ |3 |4 | -|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | -|[mistyR](problems.md#mistyr)|1.6.1 | | |1 | -|mlr3 |0.14.1 | | | | -|mlr3db |0.5.0 | | | | -|mlr3pipelines |0.4.2 | | | | -|mlr3spatial |0.3.1 | | | | -|modelsummary |1.3.0 | | | | -|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | -|MOSS |0.2.2 | | | | -|mrgsim.parallel |0.2.1 | | | | -|[mslp](problems.md#mslp) |1.0.1 |1 | | | -|multiverse |0.6.1 | | | | -|netShiny |1.0 | | | | -|NetSimR |0.1.2 | | | | -|nfl4th |1.0.2 | | | | -|nflfastR |4.5.1 | | | | -|nflseedR |1.2.0 | | | | -|nncc |1.0.0 | | | | -|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | -|onemapsgapi |1.1.0 | | | | -|[OOS](problems.md#oos) |1.0.0 | | |1 | -|origami |1.0.7 | | | | -|paramsim |0.1.0 | | | | -|[partR2](problems.md#partr2)|0.9.1 | | |1 | -|[pavo](problems.md#pavo) |2.8.0 | |1 | | -|pbapply |1.7-0 | | | | -|PCRedux |1.1-2 | | | | -|PeakSegDisk |2022.2.1 | | | | -|penaltyLearning |2020.5.13 | | | | -|pGRN |0.3.5 | | | | -|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | -|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | -|PINstimation |0.1.1 | | | | -|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | -|plumber |1.2.1 | | | | -|polle |1.2 | | | | -|POMADE |0.1.0 | | | | -|[portvine](problems.md#portvine)|1.0.2 | | |1 | -|powRICLPM |0.1.1 | | | | -|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | -|[prewas](problems.md#prewas)|1.1.1 | | |1 | -|progressr |0.13.0 | | | | -|[projpred](problems.md#projpred)|2.4.0 | | |1 | -|[promises](problems.md#promises)|1.2.0.1 | | |1 | -|Prostar |1.30.7 | | | | -|protti |0.6.0 | | | | -|PSCBS |0.66.0 | | | | -|PUMP |1.0.1 | | | | -|qape |2.0 | | | | -|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | -|qgcomp |2.10.1 | | | | -|qgcompint |0.7.0 | | | | -|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | -|rangeMapper |2.0.3 | | | | -|rBiasCorrection |0.3.4 | | | | -|receptiviti |0.1.3 | | | | -|refineR |1.5.1 | | | | -|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | -|remiod |1.0.2 | | | | -|reproducible |1.2.16 | | | | -|reval |3.1-0 | | | | -|[rgee](problems.md#rgee) |1.1.5 | | |2 | -|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | -|robust2sls |0.2.2 | | | | -|RTransferEntropy |0.2.21 | | | | -|s3fs |0.1.2 | | | | -|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | -|scBubbletree |1.0.0 | | | | -|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | -|SCtools |0.3.2.1 | | | | -|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | -|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | -|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | -|seer |1.1.8 | | | | -|semtree |0.9.18 | | | | -|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | -|[Seurat](problems.md#seurat)|4.3.0 | | |2 | -|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | -|[shiny](problems.md#shiny)|1.7.4 | | |1 | -|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | -|sigminer |2.1.9 | | | | -|Signac |1.9.0 | | | | -|[signeR](problems.md#signer)|2.0.2 | | |3 | -|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | -|simfinapi |0.2.0 | | | | -|simglm |0.8.9 | | | | -|simhelpers |0.1.2 | | | | -|sims |0.0.3 | | | | -|skewlmm |1.0.0 | | | | -|[skpr](problems.md#skpr) |1.1.6 | | |1 | -|smoots |1.1.3 | | | | -|sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude)|1.1.3 | | |1 | -|sovereign |1.2.1 | | | | -|[spaMM](problems.md#spamm)|4.1.20 | | |2 | -|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | -|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | -|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | -|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | -|specr |1.0.0 | | | | -|sperrorest |3.0.5 | | | | -|spFSR |2.0.3 | | | | -|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | -|[squat](problems.md#squat)|0.1.0 | | |1 | -|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | -|[stars](problems.md#stars)|0.6-0 | | |2 | -|startR |2.2.1 | | | | -|steps |1.3.0 | | | | -|supercells |0.9.1 | | | | -|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | -|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | -|tarchetypes |0.7.4 | | | | -|[targeted](problems.md#targeted)|0.3 | | |1 | -|targets |0.14.2 | | | | -|tcplfit2 |0.1.3 | | | | -|tealeaves |1.0.6 | | | | -|templr |0.2-0 | | | | -|[text](problems.md#text) |0.9.99.2 | | |1 | -|tglkmeans |0.3.5 | | | | -|tidyqwi |0.1.2 | | | | -|TKCat |1.0.7 | | | | -|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | -|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | -|tsfeatures |1.1 | | | | -|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | -|[txshift](problems.md#txshift)|0.3.8 | | |1 | -|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.9 | | |1 | -|[updog](problems.md#updog)|2.1.3 | | |1 | -|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | -|webdeveloper |1.0.5 | | | | -|whitewater |0.1.2 | | | | -|wildmeta |0.3.1 | | | | -|[wru](problems.md#wru) |1.0.1 | | |2 | -|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | -|yfR |1.1.0 | | | | +|package |version |error |warning |note | +|:------------------------|:---------|:-----|:-------|:----| +|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | +|alookr |0.3.7 | | | | +|alphaci |1.0.0 | | | | +|AlpsNMR |4.0.4 | | | | +|arkdb |0.0.16 | | | | +|aroma.affymetrix |3.2.1 | | | | +|aroma.cn |1.7.0 | | | | +|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | +|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | +|bamm |0.4.3 | | | | +|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | +|BatchGetSymbols |2.6.4 | | | | +|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | +|bayesian |0.0.9 | | | | +|bayesmove |0.2.1 | | | | +|bcmaps |1.1.0 | | | | +|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | +|bhmbasket |0.9.5 | | | | +|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | +|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | +|bkmrhat |1.1.3 | | | | +|[blavaan](problems.md#blavaan)|0.4-7 | | |3 | +|bolasso |0.2.0 | | | | +|[brms](problems.md#brms) |2.18.0 | | |2 | +|brpop |0.1.5 | | | | +|canaper |1.0.0 | | | | +|ceRNAnetsim |1.10.0 | | | | +|cft |1.0.0 | | | | +|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | +|civis |3.1.1 | | | | +|Clustering |1.7.7 | | | | +|codalm |0.1.2 | | | | +|[codebook](problems.md#codebook)|0.9.2 | | |3 | +|conformalInference.fd |1.1.1 | | | | +|conformalInference.multi |1.1.1 | | | | +|crossmap |0.4.0 | | | | +|CSCNet |0.1.2 | | | | +|[cSEM](problems.md#csem) |0.5.0 | | |1 | +|[CSGo](problems.md#csgo) |0.6.7 | | |1 | +|cvCovEst |1.2.0 | | | | +|dagHMM |0.1.0 | | | | +|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | +|delayed |0.4.0 | | | | +|dhReg |0.1.1 | | | | +|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | +|disk.frame |0.8.0 | | | | +|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | +|doFuture |0.12.2 | | | | +|DQAstats |0.3.2 | | | | +|[dragon](problems.md#dragon)|1.2.1 | | |1 | +|drake |7.13.4 | | | | +|drimmR |1.0.1 | | | | +|drtmle |1.1.2 | | | | +|dsos |0.1.2 | | | | +|DT |0.27 | | | | +|easyalluvial |0.3.1 | | | | +|ecic |0.0.3 | | | | +|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | +|elevatr |0.4.2 | | | | +|[envi](problems.md#envi) |0.1.17 | |1 | | +|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | +|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | +|epwshiftr |0.1.3 | | | | +|ezcox |1.0.2 | | | | +|fabletools |0.3.2 | | | | +|FAMoS |0.3.0 | | | | +|fastRhockey |0.4.0 | | | | +|[fect](problems.md#fect) |1.0.0 | | |2 | +|fiery |1.1.4 | | | | +|finbif |0.7.2 | | | | +|fitlandr |0.1.0 | | | | +|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | +|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | +|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | +|fst4pg |1.0.0 | | | | +|fundiversity |1.1.1 | | | | +|funGp |0.3.1 | | | | +|furrr |0.3.1 | | | | +|future.apply |1.10.0 | | | | +|future.batchtools |0.12.0 | | | | +|future.callr |0.8.1 | | | | +|future.tests |0.5.0 | | | | +|fxTWAPLS |0.1.2 | | | | +|genBaRcode |1.2.5 | | | | +|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | +|GetBCBData |0.7.0 | | | | +|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | +|googlePubsubR |0.0.3 | | | | +|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | +|[greed](problems.md#greed)|0.6.1 | | |2 | +|greta |0.4.3 | | | | +|gstat |2.1-0 | | | | +|GSVA |1.46.0 | | | | +|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | +|gtfs2emis |0.1.0 | | | | +|gtfs2gps |2.1-0 | | | | +|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | +|hacksig |0.1.2 | | | | +|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | +|haldensify |0.2.3 | | | | +|hoopR |1.8.0 | | | | +|[hwep](problems.md#hwep) |2.0.0 | | |2 | +|idmodelr |0.4.0 | | | | +|imagefluency |0.2.4 | | | | +|iml |0.11.1 | | | | +|incubate |1.2.0 | | | | +|[infercnv](problems.md#infercnv)|1.14.1 | |1 |3 | +|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | +|[InPAS](problems.md#inpas)|2.6.0 | | |1 | +|[interflex](problems.md#interflex)|1.2.6 | | |1 | +|ipc |0.1.4 | | | | +|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | +|isopam |1.1.0 | | | | +|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | +|JointAI |1.0.4 | | | | +|jstor |0.3.10 | | | | +|JuliaConnectoR |1.1.1 | | | | +|kernelboot |0.1.9 | | | | +|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | +|latentcor |2.0.1 | | | | +|lava |1.7.2.1 | | | | +|ldaPrototype |0.3.1 | | | | +|ldsr |0.0.2 | | | | +|lemna |1.0.0 | | | | +|LexFindR |1.0.2 | | | | +|lgr |0.4.4 | | | | +|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | +|[lightr](problems.md#lightr)|1.7.0 | | |2 | +|lmtp |1.3.1 | | | | +|LWFBrook90R |0.5.2 | | | | +|[MAI](problems.md#mai) |1.4.0 | | |1 | +|MAMS |2.0.0 | | | | +|marginaleffects |0.10.0 | | | | +|mcmcensemble |3.0.0 | | | | +|mcp |0.3.2 | | | | +|merTools |0.5.2 | | | | +|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | +|[mice](problems.md#mice) |3.15.0 | |1 | | +|[microservices](problems.md#microservices)|0.2.0 |1 | | | +|microSTASIS |0.1.0 | | | | +|migraph |0.13.2 | | | | +|mikropml |1.5.0 | | | | +|[MineICA](problems.md#mineica)|1.38.0 |1 |3 |4 | +|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | +|[mistyR](problems.md#mistyr)|1.6.1 | | |1 | +|mlr3 |0.14.1 | | | | +|mlr3db |0.5.0 | | | | +|mlr3pipelines |0.4.2 | | | | +|mlr3spatial |0.4.0 | | | | +|modelsummary |1.3.0 | | | | +|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | +|MOSS |0.2.2 | | | | +|mrgsim.parallel |0.2.1 | | | | +|[mslp](problems.md#mslp) |1.0.1 |1 | | | +|multiverse |0.6.1 | | | | +|netShiny |1.0 | | | | +|NetSimR |0.1.2 | | | | +|nfl4th |1.0.2 | | | | +|nflfastR |4.5.1 | | | | +|nflseedR |1.2.0 | | | | +|nncc |1.0.0 | | | | +|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | +|onemapsgapi |1.1.0 | | | | +|[OOS](problems.md#oos) |1.0.0 | | |1 | +|origami |1.0.7 | | | | +|paramsim |0.1.0 | | | | +|[partR2](problems.md#partr2)|0.9.1 | | |1 | +|[pavo](problems.md#pavo) |2.8.0 | |1 | | +|pbapply |1.7-0 | | | | +|PCRedux |1.1-2 | | | | +|PeakSegDisk |2022.2.1 | | | | +|penaltyLearning |2020.5.13 | | | | +|pGRN |0.3.5 | | | | +|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | +|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | +|PINstimation |0.1.1 | | | | +|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | +|plumber |1.2.1 | | | | +|polle |1.2 | | | | +|POMADE |0.1.0 | | | | +|[portvine](problems.md#portvine)|1.0.2 | | |1 | +|powRICLPM |0.1.1 | | | | +|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | +|[prewas](problems.md#prewas)|1.1.1 | | |1 | +|progressr |0.13.0 | | | | +|[projpred](problems.md#projpred)|2.4.0 | | |1 | +|[promises](problems.md#promises)|1.2.0.1 | | |1 | +|Prostar |1.30.7 | | | | +|protti |0.6.0 | | | | +|PSCBS |0.66.0 | | | | +|PUMP |1.0.1 | | | | +|qape |2.0 | | | | +|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | +|qgcomp |2.10.1 | | | | +|qgcompint |0.7.0 | | | | +|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | +|rangeMapper |2.0.3 | | | | +|rBiasCorrection |0.3.4 | | | | +|receptiviti |0.1.3 | | | | +|refineR |1.5.1 | | | | +|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | +|remiod |1.0.2 | | | | +|reproducible |1.2.16 | | | | +|reval |3.1-0 | | | | +|[rgee](problems.md#rgee) |1.1.5 | | |2 | +|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | +|robust2sls |0.2.2 | | | | +|RTransferEntropy |0.2.21 | | | | +|s3fs |0.1.2 | | | | +|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | +|scBubbletree |1.0.0 | | | | +|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | +|SCtools |0.3.2.1 | | | | +|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | +|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | +|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | +|seer |1.1.8 | | | | +|semtree |0.9.18 | | | | +|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[Seurat](problems.md#seurat)|4.3.0 | | |2 | +|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | +|[shiny](problems.md#shiny)|1.7.4 | | |1 | +|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | +|sigminer |2.1.9 | | | | +|Signac |1.9.0 | | | | +|[signeR](problems.md#signer)|2.0.2 | | |3 | +|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | +|simfinapi |0.2.0 | | | | +|simglm |0.8.9 | | | | +|simhelpers |0.1.2 | | | | +|sims |0.0.3 | | | | +|skewlmm |1.0.0 | | | | +|[skpr](problems.md#skpr) |1.1.6 | | |1 | +|smoots |1.1.3 | | | | +|sNPLS |1.0.27 | | | | +|[solitude](problems.md#solitude)|1.1.3 | | |1 | +|sovereign |1.2.1 | | | | +|[spaMM](problems.md#spamm)|4.1.20 | | |2 | +|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | +|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | +|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | +|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | +|specr |1.0.0 | | | | +|sperrorest |3.0.5 | | | | +|spFSR |2.0.3 | | | | +|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | +|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | +|[squat](problems.md#squat)|0.1.0 | | |1 | +|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | +|[stars](problems.md#stars)|0.6-0 | | |2 | +|startR |2.2.1 | | | | +|steps |1.3.0 | | | | +|supercells |0.9.1 | | | | +|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | +|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | +|tarchetypes |0.7.4 | | | | +|[targeted](problems.md#targeted)|0.3 | | |1 | +|targets |0.14.2 | | | | +|tcplfit2 |0.1.3 | | | | +|tealeaves |1.0.6 | | | | +|templr |0.2-0 | | | | +|[text](problems.md#text) |0.9.99.2 | | |1 | +|tglkmeans |0.3.5 | | | | +|tidyqwi |0.1.2 | | | | +|TKCat |1.0.7 | | | | +|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | +|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | +|tsfeatures |1.1 | | | | +|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | +|[txshift](problems.md#txshift)|0.3.8 | | |1 | +|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.10 | | |1 | +|[updog](problems.md#updog)|2.1.3 | | |1 | +|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | +|webdeveloper |1.0.5 | | | | +|whitewater |0.1.2 | | | | +|wildmeta |0.3.1 | | | | +|[wru](problems.md#wru) |1.0.1 | | |2 | +|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | +|yfR |1.1.0 | | | | diff --git a/revdep/cran.md b/revdep/cran.md index d32ba8d3..ce459500 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,14 +2,6 @@ We checked 280 reverse dependencies (261 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 1 new problems + * We saw 0 new problems * We failed to check 0 packages -Issues with CRAN packages are summarised below. - -### New problems -(This reports the first line of each new failure) - -* civis - checking package dependencies ... ERROR - diff --git a/revdep/problems.md b/revdep/problems.md index a9d81093..697970c4 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -38,8 +38,18 @@ Run `revdep_details(, "aroma.core")` for more info ## In both -* checking package dependencies ... NOTE - ``` +* checking package dependencies ...Warning: unable to access index for repository https://cloud.r-project.org/src/contrib: + ``` + cannot open URL 'https://cloud.r-project.org/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/bioc/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/bioc/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/annotation/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/data/annotation/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/experiment/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/data/experiment/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/workflows/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/workflows/src/contrib/PACKAGES' + NOTE Packages suggested but not available for checking: 'sfit', 'expectile', 'HaarSeg', 'mpcbs' ``` @@ -98,7 +108,7 @@ Run `revdep_details(, "baseballr")` for more info ... Quitting from lines 38-40 (using_statcast_pitch_data.Rmd) Error: processing vignette 'using_statcast_pitch_data.Rmd' failed with diagnostics: - Timeout was reached: [] Operation timed out after 10001 milliseconds with 0 out of 0 bytes received + HTTP error 404. --- failed re-building ‘using_statcast_pitch_data.Rmd’ SUMMARY: processing the following file failed: @@ -124,8 +134,18 @@ Run `revdep_details(, "batchtools")` for more info ## In both -* checking package dependencies ... NOTE +* checking package dependencies ...Warning: unable to access index for repository https://cloud.r-project.org/src/contrib: ``` + cannot open URL 'https://cloud.r-project.org/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/bioc/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/bioc/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/annotation/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/data/annotation/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/experiment/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/data/experiment/src/contrib/PACKAGES' + Warning: unable to access index for repository https://bioconductor.org/packages/3.16/workflows/src/contrib: + cannot open URL 'https://bioconductor.org/packages/3.16/workflows/src/contrib/PACKAGES' + NOTE Package suggested but not available for checking: ‘doMPI’ ``` @@ -228,10 +248,10 @@ Run `revdep_details(, "bistablehistory")` for more info
-* Version: 0.4-6 +* Version: 0.4-7 * GitHub: NA * Source code: https://github.com/cran/blavaan -* Date/Publication: 2023-02-11 08:50:09 UTC +* Date/Publication: 2023-03-01 12:10:02 UTC * Number of recursive dependencies: 99 Run `revdep_details(, "blavaan")` for more info @@ -249,6 +269,7 @@ Run `revdep_details(, "blavaan")` for more info ``` installed size is 89.8Mb sub-directories of 1Mb or more: + R 1.0Mb libs 87.3Mb testdata 1.4Mb ``` @@ -350,30 +371,6 @@ Run `revdep_details(, "ChromSCape")` for more info prepare_Rd: raw_counts_to_sparse_matrix.Rd:6-8: Dropping empty section \source ``` -# civis - -
- -* Version: 3.1.0 -* GitHub: https://github.com/civisanalytics/civis-r -* Source code: https://github.com/cran/civis -* Date/Publication: 2023-02-22 23:10:06 UTC -* Number of recursive dependencies: 88 - -Run `revdep_details(, "civis")` for more info - -
- -## Newly broken - -* checking package dependencies ... ERROR - ``` - Package required and available but unsuitable version: ‘future’ - - See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ - manual. - ``` - # codebook
@@ -468,8 +465,10 @@ Run `revdep_details(, "DeclareDesign")` for more info ## In both -* checking package dependencies ... NOTE +* checking package dependencies ...Warning: unable to access index for repository https://cloud.r-project.org/src/contrib: ``` + cannot open URL 'https://cloud.r-project.org/src/contrib/PACKAGES' + NOTE Package suggested but not available for checking: ‘DesignLibrary’ ``` @@ -991,10 +990,10 @@ Run `revdep_details(, "hwep")` for more info
-* Version: 1.14.0 +* Version: 1.14.1 * GitHub: https://github.com/broadinstitute/inferCNV * Source code: https://github.com/cran/infercnv -* Date/Publication: 2022-11-02 +* Date/Publication: 2023-02-26 * Number of recursive dependencies: 196 Run `revdep_details(, "infercnv")` for more info @@ -1003,6 +1002,31 @@ Run `revdep_details(, "infercnv")` for more info ## In both +* checking for code/documentation mismatches ... WARNING + ``` + Codoc mismatches from documentation object 'run': + run + Code: function(infercnv_obj, cutoff = 1, min_cells_per_gene = 3, + out_dir = NULL, window_length = 101, smooth_method = + c("pyramidinal", "runmeans", "coordinates"), + num_ref_groups = NULL, ref_subtract_use_mean_bounds = + TRUE, cluster_by_groups = FALSE, cluster_references = + TRUE, k_obs_groups = 1, hclust_method = "ward.D2", + max_centered_threshold = 3, scale_data = FALSE, HMM = + FALSE, HMM_transition_prob = 1e-06, HMM_report_by = + ... + remove_genes_at_chr_ends = FALSE, prune_outliers = + FALSE, mask_nonDE_genes = FALSE, mask_nonDE_pval = + 0.05, test.use = "wilcoxon", require_DE_all_normals = + "any", hspike_aggregate_normals = FALSE, no_plot = + FALSE, no_prelim_plot = FALSE, write_expr_matrix = + FALSE, output_format = "png", plot_chr_scale = FALSE, + chr_lengths = NULL, useRaster = TRUE, up_to_step = + 100) + Mismatches in argument default values: + Name: 'per_chr_hmm_subclusters' Code: TRUE Docs: FALSE + ``` + * checking installed package size ... NOTE ``` installed size is 5.1Mb @@ -1016,6 +1040,14 @@ Run `revdep_details(, "infercnv")` for more info See the note in ?`:::` about the use of this operator. ``` +* checking R code for possible problems ... NOTE + ``` + .whole_dataset_leiden_subclustering_per_chr: no visible binding for + global variable ‘tumor_group’ + Undefined global functions or variables: + tumor_group + ``` + # inlinedocs
@@ -1288,23 +1320,27 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 117874 Aborted (core dumped) ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 - + Running ‘testthat.R’ ERROR Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > Sys.setenv("R_TESTS" = "") - > - > library(testthat) - > library(lidR) - > test_check("lidR") - Tests using raster: terra - Tests using future: TRUE - Tests using OpenMP thread: 32 - OGR: Unsupported geometry type - OGR: Unsupported geometry type - terminate called after throwing an instance of 'std::length_error' - what(): basic_string::_S_create + Last 50 lines of output: + 3. └─lidR (local) algorithm(st_bbox(las)) + 4. └─lidR:::crop_special_its(treetops, chm, bbox) + 5. └─lidR:::raster_crop(chm, bbox) + 6. ├─sf::st_crop(raster, bbox) + 7. └─stars:::st_crop.stars(raster, bbox) + ── Error ('test-segment_trees.R:147'): Silva algorithm works with sfc ────────── + ... + 7. └─lidR:::segment_trees.LAS(las, silva2016(chm, ttops_shifted500)) + 8. └─lidR (local) algorithm(st_bbox(las)) + 9. └─lidR:::crop_special_its(treetops, chm, bbox) + 10. └─lidR:::raster_crop(chm, bbox) + 11. ├─sf::st_crop(raster, bbox) + 12. └─stars:::st_crop.stars(raster, bbox) + + [ FAIL 20 | WARN 3 | SKIP 40 | PASS 1357 ] + Error: Test failures + Execution halted ``` * checking installed package size ... NOTE @@ -1465,33 +1501,6 @@ Run `revdep_details(, "MineICA")` for more info
-## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘MineICA-Ex.R’ failed - The error most likely occurred in: - - > ### Name: IcaSet - > ### Title: Class to Contain and Describe an ICA decomposition of - > ### High-Throughput Data. - > ### Aliases: class:IcaSet IcaSet IcaSet-class [ [,ANY,ANY,IcaSet-method - > ### [,IcaSet,ANY-method [,IcaSet,ANY,ANY-method - > ### [,IcaSet,ANY,ANY,ANY-method [<- [<-,IcaSet,ANY,ANY,ANY,ANY-method - > ### [<-,IcaSet,ANY,ANY,ANY-method [<-,IcaSet,ANY,ANY-method organism - ... - > ### Keywords: classes - > - > ### ** Examples - > - > # create an instance of IcaSet - > new("IcaSet") - Error in curl::curl_fetch_memory(url, handle = handle) : - Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 0 out of -1 bytes received - Calls: new ... request_fetch -> request_fetch.write_memory -> - Execution halted - ``` - ## In both * checking running R code from vignettes ... @@ -1501,15 +1510,15 @@ Run `revdep_details(, "MineICA")` for more info Errors in running code in vignettes: when running code in ‘MineICA.Rnw’ ... - > resPath(params) - [1] "mainz/" + [25] "hgu133aPFAM" "hgu133aPMID" "hgu133aPMID2PROBE" + [28] "hgu133aPROSITE" "hgu133aREFSEQ" "hgu133aSYMBOL" + [31] "hgu133aUNIPROT" "hgu133a_dbInfo" "hgu133a_dbconn" + [34] "hgu133a_dbfile" "hgu133a_dbschema" - > resW <- writeProjByComp(icaSet = icaSetMainz, params = params, - + mart = mart, level = "genes", selCutoffWrite = 2.5) + > mart <- useMart(biomart = "ensembl", dataset = "hsapiens_gene_ensembl") When sourcing ‘MineICA.R’: - Error: task 2 failed - "Multiple cache results found. - Please clear your cache by running biomartCacheClear()" + Error: Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 120135 out of -1 bytes received Execution halted ``` @@ -1622,7 +1631,7 @@ Run `revdep_details(, "MineICA")` for more info ... Error in curl::curl_fetch_memory(url, handle = handle) : - Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 108580 out of -1 bytes received + Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 121525 out of -1 bytes received --- failed re-building ‘MineICA.Rnw’ @@ -2278,7 +2287,7 @@ Run `revdep_details(, "sctransform")` for more info * GitHub: https://github.com/Abson-dev/sdmApp * Source code: https://github.com/cran/sdmApp * Date/Publication: 2021-07-07 08:30:02 UTC -* Number of recursive dependencies: 171 +* Number of recursive dependencies: 169 Run `revdep_details(, "sdmApp")` for more info @@ -3115,10 +3124,10 @@ Run `revdep_details(, "txshift")` for more info
-* Version: 1.1.9 +* Version: 1.1.10 * GitHub: https://github.com/openbiox/UCSCXenaShiny * Source code: https://github.com/cran/UCSCXenaShiny -* Date/Publication: 2022-12-12 09:00:03 UTC +* Date/Publication: 2023-02-28 15:32:34 UTC * Number of recursive dependencies: 181 Run `revdep_details(, "UCSCXenaShiny")` for more info From b0714199e31b9cc3f5c23f7b07a1b5dbedc4268f Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 3 Mar 2023 12:25:55 +0100 Subject: [PATCH 81/88] NEWS: tweak [ci skip] --- NEWS.md | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/NEWS.md b/NEWS.md index 634ecc3a..2d791373 100644 --- a/NEWS.md +++ b/NEWS.md @@ -6,12 +6,19 @@ environment by a future. * Add option `future.onFutureCondition.keepFuture` for controlling - whether `FutureCondition` objects should have a copy of the - `Future` object or not. + whether `FutureCondition` objects should keep a copy of the + `Future` object or not. The default is to keep a copy, but if the + future carries large global objects, then the `FutureCondition` + will also be large, which can result in memory issues and slow + downs. * Add prototype of an internal event-logging framework for the purpose of profiling futures and their backends. +## Miscellaneous + + * Fix a **future.tests** check that occurred only on MS Windows. + ## Deprecated and Defunct * Add optional assertion of the internal Future `state` field. From 2eeb80bff72e3b7c565422a563873a0d424d870f Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 3 Mar 2023 14:56:59 +0100 Subject: [PATCH 82/88] README/vignette: Stop mentioning 'multiprocess' --- NEWS.md | 2 +- README.md | 44 ++++++++++++++++++++++++++++++ cran-comments.md | 44 +++++++++++++++--------------- OVERVIEW.md => incl/OVERVIEW.md | 0 inst/WORDLIST | 6 ++++ vignettes/future-1-overview.md.rsp | 2 -- 6 files changed, 73 insertions(+), 25 deletions(-) rename OVERVIEW.md => incl/OVERVIEW.md (100%) diff --git a/NEWS.md b/NEWS.md index 2d791373..91e5cbb6 100644 --- a/NEWS.md +++ b/NEWS.md @@ -30,7 +30,7 @@ # Version 1.31.0 [2023-01-31] -## Signficant Changes +## Significant Changes * Remove function `remote()`. Note that `plan(remote, ...)` has been deprecated since **future** 1.24.0 [2022-02-19] and defunct since diff --git a/README.md b/README.md index 58fe9f2c..7ac305fe 100644 --- a/README.md +++ b/README.md @@ -13,6 +13,7 @@ The purpose of the [future] package is to provide a very simple and uniform way In programming, a _future_ is an abstraction for a _value_ that may be available at some point in the future. The state of a future can either be _unresolved_ or _resolved_. As soon as it is resolved, the value is available instantaneously. If the value is queried while the future is still unresolved, the current process is _blocked_ until the future is resolved. It is possible to check whether a future is resolved or not without blocking. Exactly how and when futures are resolved depends on what strategy is used to evaluate them. For instance, a future can be resolved using a sequential strategy, which means it is resolved in the current R session. Other strategies may be to resolve futures asynchronously, for instance, by evaluating expressions in parallel on the current machine or concurrently on a compute cluster. Here is an example illustrating how the basics of futures work. First, consider the following code snippet that uses plain R code: + ```r > v <- { + cat("Hello world!\n") @@ -22,9 +23,11 @@ Hello world! > v [1] 3.14 ``` + It works by assigning the value of an expression to variable `v` and we then print the value of `v`. Moreover, when the expression for `v` is evaluated we also print a message. Here is the same code snippet modified to use futures instead: + ```r > library(future) > v %<-% { @@ -35,9 +38,11 @@ Here is the same code snippet modified to use futures instead: Hello world! [1] 3.14 ``` + The difference is in how `v` is constructed; with plain R we use `<-` whereas with futures we use `%<-%`. The other difference is that output is relayed _after_ the future is resolved (not during) and when the value is queried (see Vignette 'Outputting Text'). So why are futures useful? Because we can choose to evaluate the future expression in a separate R process asynchronously by simply switching settings as: + ```r > library(future) > plan(multisession) @@ -49,6 +54,7 @@ So why are futures useful? Because we can choose to evaluate the future express Hello world! [1] 3.14 ``` + With asynchronous futures, the current/main R process does _not_ block, which means it is available for further processing while the futures are being resolved in separate processes running in the background. In other words, futures provide a simple but yet powerful construct for parallel and / or distributed processing in R. @@ -60,6 +66,7 @@ Now, if you cannot be bothered to read all the nitty-gritty details about future ## Implicit or Explicit Futures Futures can be created either _implicitly_ or _explicitly_. In the introductory example above we used _implicit futures_ created via the `v %<-% { expr }` construct. An alternative is _explicit futures_ using the `f <- future({ expr })` and `v <- value(f)` constructs. With these, our example could alternatively be written as: + ```r > library(future) > f <- future({ @@ -124,6 +131,7 @@ Because of this, the defaults of the different strategies are such that the resu * Future _expressions are only evaluated once_. As soon as the value (or an error) has been collected it will be available for all succeeding requests. Here is an example illustrating that all assignments are done to a local environment: + ```r > plan(sequential) > a <- 1 @@ -149,6 +157,7 @@ Synchronous futures are resolved one after another and most commonly by the R pr #### Sequential Futures Sequential futures are the default unless otherwise specified. They were designed to behave as similar as possible to regular R evaluation while still fulfilling the Future API and its behaviors. Here is an example illustrating their properties: + ```r > plan(sequential) > pid <- Sys.getpid() @@ -180,6 +189,7 @@ Future 'c' ... > pid [1] 262086 ``` + Since eager sequential evaluation is taking place, each of the three futures is resolved instantaneously in the moment it is created. Note also how `pid` in the calling environment, which was assigned the process ID of the current process, is neither overwritten nor removed. This is because futures are evaluated in a local environment. Since synchronous (uni-)processing is used, future `b` is resolved by the main R process (still in a local environment), which is why the value of `b` and `pid` are the same. @@ -191,6 +201,7 @@ Next, we will turn to asynchronous futures, which are futures that are resolved #### Multisession Futures We start with multisession futures because they are supported by all operating systems. A multisession future is evaluated in a background R session running on the same machine as the calling R process. Here is our example with multisession evaluation: + ```r > plan(multisession) > pid <- Sys.getpid() @@ -222,15 +233,18 @@ Future 'c' ... > pid [1] 262086 ``` + The first thing we observe is that the values of `a`, `c` and `pid` are the same as previously. However, we notice that `b` is different from before. This is because future `b` is evaluated in a different R process and therefore it returns a different process ID. When multisession evaluation is used, the package launches a set of R sessions in the background that will serve multisession futures by evaluating their expressions as they are created. If all background sessions are busy serving other futures, the creation of the next multisession future is _blocked_ until a background session becomes available again. The total number of background processes launched is decided by the value of `availableCores()`, e.g. + ```r > availableCores() mc.cores 2 ``` + This particular result tells us that the `mc.cores` option was set such that we are allowed to use in total two (2) processes including the main process. In other words, with these settings, there will be two (2) background processes serving the multisession futures. The `availableCores()` is also agile to different options and system environment variables. For instance, if compute cluster schedulers are used (e.g. TORQUE/PBS and Slurm), they set specific environment variable specifying the number of cores that was allotted to any given job; `availableCores()` acknowledges these as well. If nothing else is specified, all available cores on the machine will be utilized, cf. `parallel::detectCores()`. For more details, please see `help("availableCores", package = "parallelly")`. @@ -252,6 +266,7 @@ On the other hand, process forking is also considered unstable in some R environ #### Cluster Futures Cluster futures evaluate expressions on an ad-hoc cluster (as implemented by the parallel package). For instance, assume you have access to three nodes `n1`, `n2` and `n3`, you can then use these for asynchronous evaluation as: + ```r > plan(cluster, workers = c("n1", "n2", "n3")) > pid <- Sys.getpid() @@ -285,10 +300,12 @@ Future 'c' ... ``` Any types of clusters that `parallel::makeCluster()` creates can be used for cluster futures. For instance, the above cluster can be explicitly set up as: + ```r cl <- parallel::makeCluster(c("n1", "n2", "n3")) plan(cluster, workers = cl) ``` + Also, it is considered good style to shut down cluster `cl` when it is no longer needed, that is, calling `parallel::stopCluster(cl)`. However, it will shut itself down if the main process is terminated. For more information on how to set up and manage such clusters, see `help("makeCluster", package = "parallel")`. Clusters created implicitly using `plan(cluster, workers = hosts)` where `hosts` is a character vector will also be shut down when the main R session terminates, or when the future strategy is changed, e.g. by calling `plan(sequential)`. @@ -309,6 +326,7 @@ will run three workers on `n1`, one on `n2`, and five on `n3`, in total nine par This far we have discussed what can be referred to as "flat topology" of futures, that is, all futures are created in and assigned to the same environment. However, there is nothing stopping us from using a "nested topology" of futures, where one set of futures may, in turn, create another set of futures internally and so on. For instance, here is an example of two "top" futures (`a` and `b`) that uses multisession evaluation and where the second future (`b`) in turn uses two internal futures: + ```r > plan(multisession) > pid <- Sys.getpid() @@ -340,6 +358,7 @@ Future 'b2' ... b.pid b1.pid b2.pid 262385 262385 262385 ``` + By inspection the process IDs, we see that there are in total three different processes involved for resolving the futures. There is the main R process (pid 262086), and there are the two processes used by `a` @@ -351,10 +370,13 @@ However, the two futures (`b1` and `b2`) that is nested by `b` are evaluated by To specify a different type of _evaluation topology_, other than the first level of futures being resolved by multisession evaluation and the second level by sequential evaluation, we can provide a list of evaluation strategies to `plan()`. First, the same evaluation strategies as above can be explicitly specified as: + ```r plan(list(multisession, sequential)) ``` + We would actually get the same behavior if we try with multiple levels of multisession evaluations; + ```r > plan(list(multisession, multisession)) [...] @@ -370,10 +392,12 @@ Future 'b2' ... b.pid b1.pid b2.pid 262516 262516 262516 ``` + The reason for this is, also here, to protect us from launching more processes than what the machine can support. Internally, this is done by setting `mc.cores = 1` such that functions like `parallel::mclapply()` will fall back to run sequentially. This is the case for both multisession and multicore evaluation. Continuing, if we start off by sequential evaluation and then use multisession evaluation for any nested futures, we get: + ```r > plan(list(sequential, multisession)) [...] @@ -389,6 +413,7 @@ Future 'b2' ... b.pid b1.pid b2.pid 262086 262664 262665 ``` + which clearly show that `a` and `b` are resolved in the calling process (pid 262086) whereas the two nested futures (`b1` and `b2`) are resolved in two separate R processes @@ -397,6 +422,7 @@ whereas the two nested futures (`b1` and `b2`) are resolved in two separate R pr Having said this, it is indeed possible to use nested multisession evaluation strategies, if we explicitly specify (read _force_) the number of cores available at each level. In order to do this we need to "tweak" the default settings, which can be done as follows: + ```r > plan(list(tweak(multisession, workers = 2), tweak(multisession, + workers = 2))) @@ -413,6 +439,7 @@ Future 'b2' ... b.pid b1.pid b2.pid 262773 262883 262882 ``` + First, we see that both `a` and `b` are resolved in different processes (pids 262772 and 262773) than the calling process @@ -427,6 +454,7 @@ For more details on working with nested futures and different evaluation strateg ### Checking A Future without Blocking It is possible to check whether a future has been resolved or not without blocking. This can be done using the `resolved(f)` function, which takes an explicit future `f` as input. If we work with implicit futures (as in all the examples above), we can use the `f <- futureOf(a)` function to retrieve the explicit future from an implicit one. For example, + ```r > plan(multisession) > a %<-% { @@ -466,6 +494,7 @@ Future 'a' ...done ## Failed Futures Sometimes the future is not what you expected. If an error occurs while evaluating a future, the error is propagated and thrown as an error in the calling environment _when the future value is requested_. For example, if we use lazy evaluation on a future that generates an error, we might see something like + ```r > plan(sequential) > b <- "hello" @@ -479,7 +508,9 @@ Everything is still ok although we have created a future that will fail. Future 'a' ... Error in log(b) : non-numeric argument to mathematical function ``` + The error is thrown each time the value is requested, that is, if we try to get the value again will generate the same error (and output): + ```r > a Future 'a' ... @@ -487,7 +518,9 @@ Error in log(b) : non-numeric argument to mathematical function In addition: Warning message: restarting interrupted promise evaluation ``` + To see the _last_ call in the call stack that gave the error, we can use the `backtrace()` function(\*) on the future, i.e. + ```r > backtrace(a) [[1]] @@ -510,6 +543,7 @@ Finally, it should be clarified that identifying globals from static code inspec ## Constraints when using Implicit Futures There is one limitation with implicit futures that does not exist for explicit ones. Because an explicit future is just like any other object in R it can be assigned anywhere/to anything. For instance, we can create several of them in a loop and assign them to a list, e.g. + ```r > plan(multisession) > f <- list() @@ -525,7 +559,9 @@ List of 3 $ : int 263105 $ : int 263104 ``` + This is _not_ possible to do when using implicit futures. This is because the `%<-%` assignment operator _cannot_ be used in all cases where the regular `<-` assignment operator can be used. It can only be used to assign future values to _environments_ (including the calling environment) much like how `assign(name, value, envir)` works. However, we can assign implicit futures to environments using _named indices_, e.g. + ```r > plan(multisession) > v <- new.env() @@ -541,9 +577,11 @@ List of 3 $ b: int 263221 $ c: int 263220 ``` + Here `as.list(v)` blocks until all futures in the environment `v` have been resolved. Then their values are collected and returned as a regular list. If _numeric indices_ are required, then _list environments_ can be used. List environments, which are implemented by the [listenv] package, are regular environments with customized subsetting operators making it possible to index them much like how lists can be indexed. By using list environments where we otherwise would use lists, we can also assign implicit futures to list-like objects using numeric indices. For example, + ```r > library(listenv) > plan(multisession) @@ -560,6 +598,7 @@ List of 3 $ : int 263335 $ : int 263336 ``` + As previously, `as.list(v)` blocks until all futures are resolved. @@ -567,17 +606,22 @@ As previously, `as.list(v)` blocks until all futures are resolved. ## Demos To see a live illustration how different types of futures are evaluated, run the Mandelbrot demo of this package. First, try with the sequential evaluation, + ```r library(future) plan(sequential) demo("mandelbrot", package = "future", ask = FALSE) ``` + which resembles how the script would run if futures were not used. Then, try multisession evaluation, which calculates the different Mandelbrot planes using parallel R processes running in the background. Try, + ```r plan(multisession) demo("mandelbrot", package = "future", ask = FALSE) ``` + Finally, if you have access to multiple machines you can try to set up a cluster of workers and use them, e.g. + ```r plan(cluster, workers = c("n2", "n5", "n6", "n6", "n9")) demo("mandelbrot", package = "future", ask = FALSE) diff --git a/cran-comments.md b/cran-comments.md index 77ea52a1..c0546f58 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,8 +1,8 @@ # CRAN submission future 1.31.0 -on 2023-01-31 +on 2023-03-03 -I've verified this submission has no negative impact on any of the 276 reverse package dependencies available on CRAN (n = 257) and Bioconductor (n = 19). +I've verified this submission has no negative impact on any of the 280 reverse package dependencies available on CRAN (n = 261) and Bioconductor (n = 19). Thank you @@ -41,48 +41,48 @@ print(res) gives ``` -── future 1.31.0: OK +── future 1.31.0-9114: OK - Build ID: future_1.31.0.tar.gz-f8efc94ad4fa463f9affccc517690397 + Build ID: future_1.31.0-9114.tar.gz-5e348ae2a35a4188b2b8e10c8c7a1ca9 Platform: Debian Linux, R-devel, clang, ISO-8859-15 locale - Submitted: 38m 17.6s ago - Build time: 38m 10.4s + Submitted: 40m 42.3s ago + Build time: 40m 2.5s 0 errors ✔ | 0 warnings ✔ | 0 notes ✔ -── future 1.31.0: OK +── future 1.31.0-9114: OK - Build ID: future_1.31.0.tar.gz-9fecff4397854eb3a27733144f38d07e + Build ID: future_1.31.0-9114.tar.gz-1845bd220cda4ba89cc7a8a9fd065e83 Platform: Fedora Linux, R-devel, GCC - Submitted: 38m 17.6s ago - Build time: 24m 9.5s + Submitted: 40m 42.3s ago + Build time: 25m 33.7s 0 errors ✔ | 0 warnings ✔ | 0 notes ✔ -── future 1.31.0: OK +── future 1.31.0-9114: OK - Build ID: future_1.31.0.tar.gz-e0200a7435c443d49a81df2c976da755 + Build ID: future_1.31.0-9114.tar.gz-e7a6c15383724b2f80239f429d5526a9 Platform: Debian Linux, R-patched, GCC - Submitted: 38m 17.6s ago - Build time: 35m 54.8s + Submitted: 40m 42.3s ago + Build time: 37m 5.5s 0 errors ✔ | 0 warnings ✔ | 0 notes ✔ -── future 1.31.0: OK +── future 1.31.0-9114: OK - Build ID: future_1.31.0.tar.gz-90adad97845a418cbff7ad20171a4d99 + Build ID: future_1.31.0-9114.tar.gz-a9a2ed5162394f14bcd004ca7b601cb2 Platform: macOS 10.13.6 High Sierra, R-release, CRAN's setup - Submitted: 38m 17.6s ago - Build time: 7m 17.3s + Submitted: 40m 42.3s ago + Build time: 8m 6.4s 0 errors ✔ | 0 warnings ✔ | 0 notes ✔ -── future 1.31.0: OK +── future 1.31.0-9114: OK - Build ID: future_1.31.0.tar.gz-4372d899916e45cc90ac72167dd7c69a + Build ID: future_1.31.0-9114.tar.gz-7f691ea7717248f6829c200b75440830 Platform: Windows Server 2022, R-release, 32/64 bit - Submitted: 38m 17.6s ago - Build time: 5m 48.8s + Submitted: 40m 42.3s ago + Build time: 6m 19.7s 0 errors ✔ | 0 warnings ✔ | 0 notes ✔ ``` diff --git a/OVERVIEW.md b/incl/OVERVIEW.md similarity index 100% rename from OVERVIEW.md rename to incl/OVERVIEW.md diff --git a/inst/WORDLIST b/inst/WORDLIST index adb9f275..3ad7ad7e 100644 --- a/inst/WORDLIST +++ b/inst/WORDLIST @@ -467,3 +467,9 @@ nopath splitted aeeba unmarshal +magrittr +cpp +globalenv +hexcode +hpp +Rscriptbd diff --git a/vignettes/future-1-overview.md.rsp b/vignettes/future-1-overview.md.rsp index 1007b04e..859aa336 100644 --- a/vignettes/future-1-overview.md.rsp +++ b/vignettes/future-1-overview.md.rsp @@ -124,8 +124,6 @@ The future package implements the following types of futures: | `multicore` | not Windows/not RStudio | forked R processes (on current machine) | `cluster` | all | external R sessions on current, local, and/or remote machines -_Comment:_ The alias strategy `multiprocess` was deprecated in future (>= 1.20.0) in favor of `multisession` and `multicore`. - The future package is designed such that support for additional strategies can be implemented as well. For instance, the [future.callr] package provides future backends that evaluates futures in a background R process utilizing the [callr] package - they work similarly to `multisession` futures but has a few advantages. Continuing, the [future.batchtools] package provides futures for all types of _cluster functions_ ("backends") that the [batchtools] package supports. Specifically, futures for evaluating R expressions via job schedulers such as Slurm, TORQUE/PBS, Oracle/Sun Grid Engine (SGE) and Load Sharing Facility (LSF) are also available. By default, future expressions are evaluated eagerly (= instantaneously) and synchronously (in the current R session). This evaluation strategy is referred to as "sequential". In this section, we will go through each of these strategies and discuss what they have in common and how they differ. From 8c6d6c90fd3a42866986f2d989bc6ba18e2b9952 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Fri, 3 Mar 2023 15:10:53 +0100 Subject: [PATCH 83/88] future 1.32.0 --- .github/workflows/future_tests.yaml | 2 +- DESCRIPTION | 2 +- NEWS.md | 2 +- cran-comments.md | 4 ++-- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/.github/workflows/future_tests.yaml b/.github/workflows/future_tests.yaml index 15179569..cd3f4517 100644 --- a/.github/workflows/future_tests.yaml +++ b/.github/workflows/future_tests.yaml @@ -21,6 +21,7 @@ jobs: - { plan: 'multisession' } - { plan: 'sequential' } - { plan: 'future.batchtools::batchtools_local' } + - { plan: 'future.batchtools::batchtools_bash' } - { plan: 'future.callr::callr' } env: @@ -28,7 +29,6 @@ jobs: RSPM: https://packagemanager.rstudio.com/cran/__linux__/focal/latest R_REMOTES_NO_ERRORS_FROM_WARNINGS: true ## R CMD check - _R_CHECK_LENGTH_1_CONDITION_: true _R_CHECK_LENGTH_1_LOGIC2_: true _R_CHECK_MATRIX_DATA_: true _R_CHECK_CRAN_INCOMING_: false diff --git a/DESCRIPTION b/DESCRIPTION index 7dd0e5a2..bf5481ef 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,5 +1,5 @@ Package: future -Version: 1.31.0-9114 +Version: 1.32.0 Title: Unified Parallel and Distributed Processing in R for Everyone Imports: digest, diff --git a/NEWS.md b/NEWS.md index 91e5cbb6..e63460b8 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# Version (development version) +# Version 1.312.0 [2023-03-03] ## New Features diff --git a/cran-comments.md b/cran-comments.md index c0546f58..b55355ff 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,4 +1,4 @@ -# CRAN submission future 1.31.0 +# CRAN submission future 1.32.0 on 2023-03-03 @@ -19,7 +19,7 @@ The package has been verified using `R CMD check --as-cran` on: | 3.6.x | L | | | | | 4.0.x | L | | | | | 4.1.x | L M W | M | | | -| 4.2.x | L M W | L W | M1 W | W* | +| 4.2.x | L M W | L W | M1 W | | | devel | L M W | L | M1 W | | _Legend: OS: L = Linux, M = macOS, M1 = macOS M1, W = Windows, * = msys2_ From 1d285e58f3d906e48ae480e05b381027c6d45c2c Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Sat, 4 Mar 2023 14:05:44 -0800 Subject: [PATCH 84/88] REVDEP: 280 revdep packages with R_FUTURE_STATE_ONINVALID=error, R_FUTURE_RNG_ONMISUSE=error, R_FUTURE_GLOBALENV_ONMISUSE=error [ci skip] --- revdep/README.md | 592 ++++++++++++++++++------------------ revdep/cran.md | 22 +- revdep/problems.md | 736 +++++++++++++++++++++++++++++++++++++++++---- 3 files changed, 1006 insertions(+), 344 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 99c92408..6683bf7c 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,304 +10,314 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-03-02 | +|date |2023-03-04 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies -|package |old |new |Δ | -|:----------|:------|:-----------|:--| -|future |1.31.0 |1.31.0-9114 |* | -|codetools |0.2-19 |0.2-19 | | -|digest |0.6.31 |0.6.31 | | -|globals |0.16.2 |0.16.2 | | -|listenv |0.9.0 |0.9.0 | | -|parallelly |1.34.0 |1.34.0 | | +|package |old |new |Δ | +|:----------|:------|:------|:--| +|future |1.31.0 |1.32.0 |* | +|codetools |0.2-19 |0.2-19 | | +|digest |0.6.31 |0.6.31 | | +|globals |0.16.2 |0.16.2 | | +|listenv |0.9.0 |0.9.0 | | +|parallelly |1.34.0 |1.34.0 | | # Revdeps +## New problems (5) + +|package |version |error |warning |note | +|:------------|:-------|:------|:-------|:----| +|[alookr](problems.md#alookr)|0.3.7 |__+1__ | | | +|[civis](problems.md#civis)|3.1.1 |__+1__ | | | +|[future.tests](problems.md#futuretests)|0.5.0 |__+1__ | | | +|[PINstimation](problems.md#pinstimation)|0.1.1 |__+1__ | | | +|[semtree](problems.md#semtree)|0.9.18 |__+1__ | | | + ## All (280) -|package |version |error |warning |note | -|:------------------------|:---------|:-----|:-------|:----| -|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | -|alookr |0.3.7 | | | | -|alphaci |1.0.0 | | | | -|AlpsNMR |4.0.4 | | | | -|arkdb |0.0.16 | | | | -|aroma.affymetrix |3.2.1 | | | | -|aroma.cn |1.7.0 | | | | -|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | -|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | -|bamm |0.4.3 | | | | -|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | -|BatchGetSymbols |2.6.4 | | | | -|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | -|bayesian |0.0.9 | | | | -|bayesmove |0.2.1 | | | | -|bcmaps |1.1.0 | | | | -|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | -|bhmbasket |0.9.5 | | | | -|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | -|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | -|bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan)|0.4-7 | | |3 | -|bolasso |0.2.0 | | | | -|[brms](problems.md#brms) |2.18.0 | | |2 | -|brpop |0.1.5 | | | | -|canaper |1.0.0 | | | | -|ceRNAnetsim |1.10.0 | | | | -|cft |1.0.0 | | | | -|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | -|civis |3.1.1 | | | | -|Clustering |1.7.7 | | | | -|codalm |0.1.2 | | | | -|[codebook](problems.md#codebook)|0.9.2 | | |3 | -|conformalInference.fd |1.1.1 | | | | -|conformalInference.multi |1.1.1 | | | | -|crossmap |0.4.0 | | | | -|CSCNet |0.1.2 | | | | -|[cSEM](problems.md#csem) |0.5.0 | | |1 | -|[CSGo](problems.md#csgo) |0.6.7 | | |1 | -|cvCovEst |1.2.0 | | | | -|dagHMM |0.1.0 | | | | -|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | -|delayed |0.4.0 | | | | -|dhReg |0.1.1 | | | | -|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | -|disk.frame |0.8.0 | | | | -|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | -|doFuture |0.12.2 | | | | -|DQAstats |0.3.2 | | | | -|[dragon](problems.md#dragon)|1.2.1 | | |1 | -|drake |7.13.4 | | | | -|drimmR |1.0.1 | | | | -|drtmle |1.1.2 | | | | -|dsos |0.1.2 | | | | -|DT |0.27 | | | | -|easyalluvial |0.3.1 | | | | -|ecic |0.0.3 | | | | -|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | -|elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.17 | |1 | | -|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | -|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | -|epwshiftr |0.1.3 | | | | -|ezcox |1.0.2 | | | | -|fabletools |0.3.2 | | | | -|FAMoS |0.3.0 | | | | -|fastRhockey |0.4.0 | | | | -|[fect](problems.md#fect) |1.0.0 | | |2 | -|fiery |1.1.4 | | | | -|finbif |0.7.2 | | | | -|fitlandr |0.1.0 | | | | -|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | -|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | -|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | -|fst4pg |1.0.0 | | | | -|fundiversity |1.1.1 | | | | -|funGp |0.3.1 | | | | -|furrr |0.3.1 | | | | -|future.apply |1.10.0 | | | | -|future.batchtools |0.12.0 | | | | -|future.callr |0.8.1 | | | | -|future.tests |0.5.0 | | | | -|fxTWAPLS |0.1.2 | | | | -|genBaRcode |1.2.5 | | | | -|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | -|GetBCBData |0.7.0 | | | | -|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | -|googlePubsubR |0.0.3 | | | | -|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | -|[greed](problems.md#greed)|0.6.1 | | |2 | -|greta |0.4.3 | | | | -|gstat |2.1-0 | | | | -|GSVA |1.46.0 | | | | -|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | -|gtfs2emis |0.1.0 | | | | -|gtfs2gps |2.1-0 | | | | -|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | -|hacksig |0.1.2 | | | | -|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | -|haldensify |0.2.3 | | | | -|hoopR |1.8.0 | | | | -|[hwep](problems.md#hwep) |2.0.0 | | |2 | -|idmodelr |0.4.0 | | | | -|imagefluency |0.2.4 | | | | -|iml |0.11.1 | | | | -|incubate |1.2.0 | | | | -|[infercnv](problems.md#infercnv)|1.14.1 | |1 |3 | -|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | -|[InPAS](problems.md#inpas)|2.6.0 | | |1 | -|[interflex](problems.md#interflex)|1.2.6 | | |1 | -|ipc |0.1.4 | | | | -|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | -|isopam |1.1.0 | | | | -|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | -|JointAI |1.0.4 | | | | -|jstor |0.3.10 | | | | -|JuliaConnectoR |1.1.1 | | | | -|kernelboot |0.1.9 | | | | -|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | -|latentcor |2.0.1 | | | | -|lava |1.7.2.1 | | | | -|ldaPrototype |0.3.1 | | | | -|ldsr |0.0.2 | | | | -|lemna |1.0.0 | | | | -|LexFindR |1.0.2 | | | | -|lgr |0.4.4 | | | | -|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | -|[lightr](problems.md#lightr)|1.7.0 | | |2 | -|lmtp |1.3.1 | | | | -|LWFBrook90R |0.5.2 | | | | -|[MAI](problems.md#mai) |1.4.0 | | |1 | -|MAMS |2.0.0 | | | | -|marginaleffects |0.10.0 | | | | -|mcmcensemble |3.0.0 | | | | -|mcp |0.3.2 | | | | -|merTools |0.5.2 | | | | -|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | -|[mice](problems.md#mice) |3.15.0 | |1 | | -|[microservices](problems.md#microservices)|0.2.0 |1 | | | -|microSTASIS |0.1.0 | | | | -|migraph |0.13.2 | | | | -|mikropml |1.5.0 | | | | -|[MineICA](problems.md#mineica)|1.38.0 |1 |3 |4 | -|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | -|[mistyR](problems.md#mistyr)|1.6.1 | | |1 | -|mlr3 |0.14.1 | | | | -|mlr3db |0.5.0 | | | | -|mlr3pipelines |0.4.2 | | | | -|mlr3spatial |0.4.0 | | | | -|modelsummary |1.3.0 | | | | -|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | -|MOSS |0.2.2 | | | | -|mrgsim.parallel |0.2.1 | | | | -|[mslp](problems.md#mslp) |1.0.1 |1 | | | -|multiverse |0.6.1 | | | | -|netShiny |1.0 | | | | -|NetSimR |0.1.2 | | | | -|nfl4th |1.0.2 | | | | -|nflfastR |4.5.1 | | | | -|nflseedR |1.2.0 | | | | -|nncc |1.0.0 | | | | -|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | -|onemapsgapi |1.1.0 | | | | -|[OOS](problems.md#oos) |1.0.0 | | |1 | -|origami |1.0.7 | | | | -|paramsim |0.1.0 | | | | -|[partR2](problems.md#partr2)|0.9.1 | | |1 | -|[pavo](problems.md#pavo) |2.8.0 | |1 | | -|pbapply |1.7-0 | | | | -|PCRedux |1.1-2 | | | | -|PeakSegDisk |2022.2.1 | | | | -|penaltyLearning |2020.5.13 | | | | -|pGRN |0.3.5 | | | | -|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | -|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | -|PINstimation |0.1.1 | | | | -|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | -|plumber |1.2.1 | | | | -|polle |1.2 | | | | -|POMADE |0.1.0 | | | | -|[portvine](problems.md#portvine)|1.0.2 | | |1 | -|powRICLPM |0.1.1 | | | | -|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | -|[prewas](problems.md#prewas)|1.1.1 | | |1 | -|progressr |0.13.0 | | | | -|[projpred](problems.md#projpred)|2.4.0 | | |1 | -|[promises](problems.md#promises)|1.2.0.1 | | |1 | -|Prostar |1.30.7 | | | | -|protti |0.6.0 | | | | -|PSCBS |0.66.0 | | | | -|PUMP |1.0.1 | | | | -|qape |2.0 | | | | -|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | -|qgcomp |2.10.1 | | | | -|qgcompint |0.7.0 | | | | -|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | -|rangeMapper |2.0.3 | | | | -|rBiasCorrection |0.3.4 | | | | -|receptiviti |0.1.3 | | | | -|refineR |1.5.1 | | | | -|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | -|remiod |1.0.2 | | | | -|reproducible |1.2.16 | | | | -|reval |3.1-0 | | | | -|[rgee](problems.md#rgee) |1.1.5 | | |2 | -|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | -|robust2sls |0.2.2 | | | | -|RTransferEntropy |0.2.21 | | | | -|s3fs |0.1.2 | | | | -|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | -|scBubbletree |1.0.0 | | | | -|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | -|SCtools |0.3.2.1 | | | | -|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | -|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | -|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | -|seer |1.1.8 | | | | -|semtree |0.9.18 | | | | -|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | -|[Seurat](problems.md#seurat)|4.3.0 | | |2 | -|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | -|[shiny](problems.md#shiny)|1.7.4 | | |1 | -|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | -|sigminer |2.1.9 | | | | -|Signac |1.9.0 | | | | -|[signeR](problems.md#signer)|2.0.2 | | |3 | -|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | -|simfinapi |0.2.0 | | | | -|simglm |0.8.9 | | | | -|simhelpers |0.1.2 | | | | -|sims |0.0.3 | | | | -|skewlmm |1.0.0 | | | | -|[skpr](problems.md#skpr) |1.1.6 | | |1 | -|smoots |1.1.3 | | | | -|sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude)|1.1.3 | | |1 | -|sovereign |1.2.1 | | | | -|[spaMM](problems.md#spamm)|4.1.20 | | |2 | -|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | -|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | -|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | -|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | -|specr |1.0.0 | | | | -|sperrorest |3.0.5 | | | | -|spFSR |2.0.3 | | | | -|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | -|[squat](problems.md#squat)|0.1.0 | | |1 | -|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | -|[stars](problems.md#stars)|0.6-0 | | |2 | -|startR |2.2.1 | | | | -|steps |1.3.0 | | | | -|supercells |0.9.1 | | | | -|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | -|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | -|tarchetypes |0.7.4 | | | | -|[targeted](problems.md#targeted)|0.3 | | |1 | -|targets |0.14.2 | | | | -|tcplfit2 |0.1.3 | | | | -|tealeaves |1.0.6 | | | | -|templr |0.2-0 | | | | -|[text](problems.md#text) |0.9.99.2 | | |1 | -|tglkmeans |0.3.5 | | | | -|tidyqwi |0.1.2 | | | | -|TKCat |1.0.7 | | | | -|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | -|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | -|tsfeatures |1.1 | | | | -|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | -|[txshift](problems.md#txshift)|0.3.8 | | |1 | -|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.10 | | |1 | -|[updog](problems.md#updog)|2.1.3 | | |1 | -|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | -|webdeveloper |1.0.5 | | | | -|whitewater |0.1.2 | | | | -|wildmeta |0.3.1 | | | | -|[wru](problems.md#wru) |1.0.1 | | |2 | -|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | -|yfR |1.1.0 | | | | +|package |version |error |warning |note | +|:------------------------|:---------|:------|:-------|:----| +|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | +|[alookr](problems.md#alookr)|0.3.7 |__+1__ | | | +|alphaci |1.0.0 | | | | +|[AlpsNMR](problems.md#alpsnmr)|4.0.4 |1 | | | +|arkdb |0.0.16 | | | | +|aroma.affymetrix |3.2.1 | | | | +|aroma.cn |1.7.0 | | | | +|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | +|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | +|bamm |0.4.3 | | | | +|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | +|BatchGetSymbols |2.6.4 | | | | +|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | +|bayesian |0.0.9 | | | | +|bayesmove |0.2.1 | | | | +|bcmaps |1.1.0 | | | | +|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | +|bhmbasket |0.9.5 | | | | +|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | +|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | +|bkmrhat |1.1.3 | | | | +|[blavaan](problems.md#blavaan)|0.4-7 | | |3 | +|bolasso |0.2.0 | | | | +|[brms](problems.md#brms) |2.18.0 | | |2 | +|brpop |0.1.5 | | | | +|canaper |1.0.0 | | | | +|ceRNAnetsim |1.10.0 | | | | +|cft |1.0.0 | | | | +|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | +|[civis](problems.md#civis)|3.1.1 |__+1__ | | | +|Clustering |1.7.7 | | | | +|codalm |0.1.2 | | | | +|[codebook](problems.md#codebook)|0.9.2 |1 | |3 | +|conformalInference.fd |1.1.1 | | | | +|conformalInference.multi |1.1.1 | | | | +|crossmap |0.4.0 | | | | +|CSCNet |0.1.2 | | | | +|[cSEM](problems.md#csem) |0.5.0 |1 | |1 | +|[CSGo](problems.md#csgo) |0.6.7 | | |1 | +|cvCovEst |1.2.0 | | | | +|dagHMM |0.1.0 | | | | +|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | +|delayed |0.4.0 | | | | +|dhReg |0.1.1 | | | | +|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | +|disk.frame |0.8.0 | | | | +|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | +|doFuture |0.12.2 | | | | +|DQAstats |0.3.2 | | | | +|[dragon](problems.md#dragon)|1.2.1 | | |1 | +|drake |7.13.4 | | | | +|drimmR |1.0.1 | | | | +|drtmle |1.1.2 | | | | +|dsos |0.1.2 | | | | +|DT |0.27 | | | | +|easyalluvial |0.3.1 | | | | +|ecic |0.0.3 | | | | +|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | +|elevatr |0.4.2 | | | | +|[envi](problems.md#envi) |0.1.17 | |1 | | +|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | +|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | +|epwshiftr |0.1.3 | | | | +|ezcox |1.0.2 | | | | +|fabletools |0.3.2 | | | | +|FAMoS |0.3.0 | | | | +|fastRhockey |0.4.0 | | | | +|[fect](problems.md#fect) |1.0.0 | | |2 | +|fiery |1.1.4 | | | | +|finbif |0.7.2 | | | | +|fitlandr |0.1.0 | | | | +|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | +|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | +|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | +|fst4pg |1.0.0 | | | | +|fundiversity |1.1.1 | | | | +|funGp |0.3.1 | | | | +|furrr |0.3.1 | | | | +|future.apply |1.10.0 | | | | +|future.batchtools |0.12.0 | | | | +|future.callr |0.8.1 | | | | +|[future.tests](problems.md#futuretests)|0.5.0 |__+1__ | | | +|fxTWAPLS |0.1.2 | | | | +|genBaRcode |1.2.5 | | | | +|[geocmeans](problems.md#geocmeans)|0.3.3 |1 | |1 | +|GetBCBData |0.7.0 | | | | +|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | +|googlePubsubR |0.0.4 | | | | +|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | +|[greed](problems.md#greed)|0.6.1 | | |2 | +|greta |0.4.3 | | | | +|gstat |2.1-0 | | | | +|GSVA |1.46.0 | | | | +|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | +|[gtfs2emis](problems.md#gtfs2emis)|0.1.0 |1 | | | +|gtfs2gps |2.1-0 | | | | +|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | +|hacksig |0.1.2 | | | | +|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | +|haldensify |0.2.3 | | | | +|hoopR |1.8.0 | | | | +|[hwep](problems.md#hwep) |2.0.0 | | |2 | +|idmodelr |0.4.0 | | | | +|imagefluency |0.2.4 | | | | +|iml |0.11.1 | | | | +|incubate |1.2.0 | | | | +|[infercnv](problems.md#infercnv)|1.14.1 | |1 |3 | +|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | +|[InPAS](problems.md#inpas)|2.6.0 | | |1 | +|[interflex](problems.md#interflex)|1.2.6 | | |1 | +|ipc |0.1.4 | | | | +|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | +|isopam |1.1.0 | | | | +|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | +|JointAI |1.0.4 | | | | +|jstor |0.3.10 | | | | +|JuliaConnectoR |1.1.1 | | | | +|kernelboot |0.1.9 | | | | +|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | +|latentcor |2.0.1 | | | | +|[lava](problems.md#lava) |1.7.2.1 |2 | | | +|ldaPrototype |0.3.1 | | | | +|ldsr |0.0.2 | | | | +|lemna |1.0.0 | | | | +|LexFindR |1.0.2 | | | | +|lgr |0.4.4 | | | | +|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | +|[lightr](problems.md#lightr)|1.7.0 | | |2 | +|lmtp |1.3.1 | | | | +|LWFBrook90R |0.5.2 | | | | +|[MAI](problems.md#mai) |1.4.0 | | |1 | +|MAMS |2.0.0 | | | | +|marginaleffects |0.10.0 | | | | +|mcmcensemble |3.0.0 | | | | +|mcp |0.3.2 | | | | +|merTools |0.5.2 | | | | +|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | +|[mice](problems.md#mice) |3.15.0 | |1 | | +|[microservices](problems.md#microservices)|0.2.0 |1 | | | +|microSTASIS |0.1.0 | | | | +|migraph |0.13.2 | | | | +|mikropml |1.5.0 | | | | +|[MineICA](problems.md#mineica)|1.38.0 |1 |3 |4 | +|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | +|[mistyR](problems.md#mistyr)|1.6.1 |1 | |1 | +|mlr3 |0.14.1 | | | | +|mlr3db |0.5.0 | | | | +|mlr3pipelines |0.4.2 | | | | +|mlr3spatial |0.4.0 | | | | +|modelsummary |1.3.0 | | | | +|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | +|MOSS |0.2.2 | | | | +|mrgsim.parallel |0.2.1 | | | | +|[mslp](problems.md#mslp) |1.0.1 |1 | | | +|multiverse |0.6.1 | | | | +|netShiny |1.0 | | | | +|NetSimR |0.1.2 | | | | +|nfl4th |1.0.2 | | | | +|nflfastR |4.5.1 | | | | +|nflseedR |1.2.0 | | | | +|nncc |1.0.0 | | | | +|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | +|onemapsgapi |1.1.0 | | | | +|[OOS](problems.md#oos) |1.0.0 |2 | |1 | +|origami |1.0.7 | | | | +|paramsim |0.1.0 | | | | +|[partR2](problems.md#partr2)|0.9.1 | | |1 | +|[pavo](problems.md#pavo) |2.8.0 | |1 | | +|pbapply |1.7-0 | | | | +|PCRedux |1.1-2 | | | | +|PeakSegDisk |2022.2.1 | | | | +|penaltyLearning |2020.5.13 | | | | +|pGRN |0.3.5 | | | | +|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | +|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | +|[PINstimation](problems.md#pinstimation)|0.1.1 |__+1__ | | | +|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | +|plumber |1.2.1 | | | | +|polle |1.2 | | | | +|POMADE |0.1.0 | | | | +|[portvine](problems.md#portvine)|1.0.2 | | |1 | +|powRICLPM |0.1.1 | | | | +|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | +|[prewas](problems.md#prewas)|1.1.1 |1 | |1 | +|progressr |0.13.0 | | | | +|[projpred](problems.md#projpred)|2.4.0 | | |1 | +|[promises](problems.md#promises)|1.2.0.1 | | |1 | +|Prostar |1.30.7 | | | | +|protti |0.6.0 | | | | +|PSCBS |0.66.0 | | | | +|PUMP |1.0.1 | | | | +|qape |2.0 | | | | +|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | +|qgcomp |2.10.1 | | | | +|qgcompint |0.7.0 | | | | +|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | +|rangeMapper |2.0.3 | | | | +|rBiasCorrection |0.3.4 | | | | +|receptiviti |0.1.3 | | | | +|refineR |1.5.1 | | | | +|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | +|remiod |1.0.2 | | | | +|[reproducible](problems.md#reproducible)|1.2.16 |1 | | | +|reval |3.1-0 | | | | +|[rgee](problems.md#rgee) |1.1.5 | | |2 | +|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | +|robust2sls |0.2.2 | | | | +|RTransferEntropy |0.2.21 | | | | +|s3fs |0.1.3 | | | | +|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | +|scBubbletree |1.0.0 | | | | +|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | +|SCtools |0.3.2.1 | | | | +|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | +|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | +|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | +|seer |1.1.8 | | | | +|[semtree](problems.md#semtree)|0.9.18 |__+1__ | | | +|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[Seurat](problems.md#seurat)|4.3.0 | | |2 | +|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | +|[shiny](problems.md#shiny)|1.7.4 | | |1 | +|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | +|sigminer |2.1.9 | | | | +|Signac |1.9.0 | | | | +|[signeR](problems.md#signer)|2.0.2 | | |3 | +|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | +|simfinapi |0.2.3 | | | | +|simglm |0.8.9 | | | | +|[simhelpers](problems.md#simhelpers)|0.1.2 |1 | | | +|sims |0.0.3 | | | | +|skewlmm |1.0.0 | | | | +|[skpr](problems.md#skpr) |1.1.6 | | |1 | +|smoots |1.1.3 | | | | +|sNPLS |1.0.27 | | | | +|[solitude](problems.md#solitude)|1.1.3 | | |1 | +|sovereign |1.2.1 | | | | +|[spaMM](problems.md#spamm)|4.2.1 | | |2 | +|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | +|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 |2 | |1 | +|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | +|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | +|specr |1.0.0 | | | | +|sperrorest |3.0.5 | | | | +|spFSR |2.0.3 | | | | +|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | +|[spNetwork](problems.md#spnetwork)|0.4.3.6 |1 | |1 | +|[squat](problems.md#squat)|0.1.0 | | |1 | +|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | +|[stars](problems.md#stars)|0.6-0 | | |2 | +|startR |2.2.1 | | | | +|steps |1.3.0 | | | | +|supercells |0.9.1 | | | | +|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | +|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | +|tarchetypes |0.7.4 | | | | +|[targeted](problems.md#targeted)|0.3 | | |1 | +|targets |0.14.2 | | | | +|tcplfit2 |0.1.3 | | | | +|tealeaves |1.0.6 | | | | +|templr |0.2-0 | | | | +|[text](problems.md#text) |0.9.99.2 | | |1 | +|tglkmeans |0.3.5 | | | | +|tidyqwi |0.1.2 | | | | +|TKCat |1.0.7 | | | | +|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | +|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | +|tsfeatures |1.1 | | | | +|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | +|[txshift](problems.md#txshift)|0.3.8 | | |1 | +|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.10 | | |1 | +|[updog](problems.md#updog)|2.1.3 | | |1 | +|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | +|webdeveloper |1.0.5 | | | | +|whitewater |0.1.2 | | | | +|wildmeta |0.3.1 | | | | +|[wru](problems.md#wru) |1.0.1 | | |2 | +|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | +|yfR |1.1.0 | | | | diff --git a/revdep/cran.md b/revdep/cran.md index ce459500..750961ba 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,6 +2,26 @@ We checked 280 reverse dependencies (261 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 0 new problems + * We saw 5 new problems * We failed to check 0 packages +Issues with CRAN packages are summarised below. + +### New problems +(This reports the first line of each new failure) + +* alookr + checking examples ... ERROR + +* civis + checking tests ... + +* future.tests + checking tests ... + +* PINstimation + checking re-building of vignette outputs ... ERROR + +* semtree + checking tests ... + diff --git a/revdep/problems.md b/revdep/problems.md index 697970c4..148d75cc 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -22,6 +22,88 @@ Run `revdep_details(, "AIPW")` for more info All declared Imports should be used. ``` +# alookr + +
+ +* Version: 0.3.7 +* GitHub: https://github.com/choonghyunryu/alookr +* Source code: https://github.com/cran/alookr +* Date/Publication: 2022-06-12 15:30:02 UTC +* Number of recursive dependencies: 158 + +Run `revdep_details(, "alookr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘alookr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: run_models + > ### Title: Fit binary classification model + > ### Aliases: run_models + > + > ### ** Examples + > + > library(dplyr) + ... + 10. │ ├─purrr:::call_with_cleanup(...) + 11. │ └─alookr (local) .f(.x[[i]], ...) + 12. │ ├─future::value(.x) + 13. │ └─future:::value.Future(.x) + 14. │ └─future:::signalConditions(...) + 15. │ └─base::stop(condition) + 16. └─purrr (local) ``(``) + 17. └─cli::cli_abort(...) + 18. └─rlang::abort(...) + Execution halted + ``` + +# AlpsNMR + +
+ +* Version: 4.0.4 +* GitHub: https://github.com/sipss/AlpsNMR +* Source code: https://github.com/cran/AlpsNMR +* Date/Publication: 2023-02-16 +* Number of recursive dependencies: 169 + +Run `revdep_details(, "AlpsNMR")` for more info + +
+ +## In both + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + --- re-building ‘Vig01-introduction-to-alpsnmr.Rmd’ using rmarkdown + Warning in has_utility("pdfcrop") : + pdfcrop not installed or not in PATH + sh: pdfcrop: command not found + Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : + error in running command + sh: pdfcrop: command not found + Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : + error in running command + ... + Warning: (fancyhdr) \setlength{\headheight}{46.27916pt}. + Warning: (fancyhdr) You might also make \topmargin smaller to compensate: + Warning: (fancyhdr) \addtolength{\topmargin}{-3.60004pt}. + --- finished re-building ‘Vig02-handling-metadata-and-annotations.Rmd’ + + SUMMARY: processing the following file failed: + ‘Vig01b-introduction-to-alpsnmr-old-api.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + # aroma.core
@@ -38,18 +120,8 @@ Run `revdep_details(, "aroma.core")` for more info ## In both -* checking package dependencies ...Warning: unable to access index for repository https://cloud.r-project.org/src/contrib: +* checking package dependencies ... NOTE ``` - cannot open URL 'https://cloud.r-project.org/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/bioc/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/bioc/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/annotation/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/data/annotation/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/experiment/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/data/experiment/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/workflows/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/workflows/src/contrib/PACKAGES' - NOTE Packages suggested but not available for checking: 'sfit', 'expectile', 'HaarSeg', 'mpcbs' ``` @@ -134,18 +206,8 @@ Run `revdep_details(, "batchtools")` for more info ## In both -* checking package dependencies ...Warning: unable to access index for repository https://cloud.r-project.org/src/contrib: +* checking package dependencies ... NOTE ``` - cannot open URL 'https://cloud.r-project.org/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/bioc/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/bioc/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/annotation/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/data/annotation/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/data/experiment/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/data/experiment/src/contrib/PACKAGES' - Warning: unable to access index for repository https://bioconductor.org/packages/3.16/workflows/src/contrib: - cannot open URL 'https://bioconductor.org/packages/3.16/workflows/src/contrib/PACKAGES' - NOTE Package suggested but not available for checking: ‘doMPI’ ``` @@ -371,6 +433,47 @@ Run `revdep_details(, "ChromSCape")` for more info prepare_Rd: raw_counts_to_sparse_matrix.Rd:6-8: Dropping empty section \source ``` +# civis + +
+ +* Version: 3.1.1 +* GitHub: https://github.com/civisanalytics/civis-r +* Source code: https://github.com/cran/civis +* Date/Publication: 2023-02-28 08:02:29 UTC +* Number of recursive dependencies: 88 + +Run `revdep_details(, "civis")` for more info + +
+ +## Newly broken + +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(civis) + > + > test_check("civis") + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 1058 ] + + ... + Backtrace: + ▆ + 1. ├─civis::cancel(fut) + 2. └─civis:::cancel.CivisFuture(fut) + 3. ├─base::`$<-`(`*tmp*`, "state", value = ``) + 4. └─future:::`$<-.Future`(`*tmp*`, "state", value = ``) + + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 1058 ] + Error: Test failures + Execution halted + ``` + # codebook
@@ -387,6 +490,31 @@ Run `revdep_details(, "codebook")` for more info ## In both +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + --- re-building ‘codebook.Rmd’ using rmarkdown + Failed with error: 'there is no package called 'GGally'' + Failed with error: 'there is no package called 'GGally'' + Failed with error: 'there is no package called 'GGally'' + Failed with error: 'there is no package called 'GGally'' + Quitting from lines 85-86 (codebook.Rmd) + Error: processing vignette 'codebook.Rmd' failed with diagnostics: + UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". + --- failed re-building ‘codebook.Rmd’ + ... + Failed with error: 'there is no package called 'GGally'' + Failed with error: 'there is no package called 'GGally'' + Failed with error: 'there is no package called 'GGally'' + --- finished re-building ‘codebook_tutorial.Rmd’ + + SUMMARY: processing the following file failed: + ‘codebook.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + * checking package dependencies ... NOTE ``` Package suggested but not available for checking: ‘userfriendlyscience’ @@ -420,6 +548,31 @@ Run `revdep_details(, "cSEM")` for more info ## In both +* checking examples ... ERROR + ``` + Running examples in ‘cSEM-Ex.R’ failed + The error most likely occurred in: + + > ### Name: resampleData + > ### Title: Resample data + > ### Aliases: resampleData + > + > ### ** Examples + > + > # =========================================================================== + ... + Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : + data length is not a multiple of split variable + Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : + data length is not a multiple of split variable + Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : + data length is not a multiple of split variable + Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : + data length is not a multiple of split variable + Error: UNRELIABLE VALUE: One of the ‘future.apply’ iterations (‘future_lapply-1’) unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". + Execution halted + ``` + * checking dependencies in R code ... NOTE ``` Namespace in Imports field not imported from: ‘Rdpack’ @@ -465,10 +618,8 @@ Run `revdep_details(, "DeclareDesign")` for more info ## In both -* checking package dependencies ...Warning: unable to access index for repository https://cloud.r-project.org/src/contrib: +* checking package dependencies ... NOTE ``` - cannot open URL 'https://cloud.r-project.org/src/contrib/PACKAGES' - NOTE Package suggested but not available for checking: ‘DesignLibrary’ ``` @@ -772,6 +923,47 @@ Run `revdep_details(, "forecastML")` for more info All declared Imports should be used. ``` +# future.tests + +
+ +* Version: 0.5.0 +* GitHub: https://github.com/HenrikBengtsson/future.tests +* Source code: https://github.com/cran/future.tests +* Date/Publication: 2022-12-16 08:20:02 UTC +* Number of recursive dependencies: 15 + +Run `revdep_details(, "future.tests")` for more info + +
+ +## Newly broken + +* checking tests ... + ``` + Running ‘Test-class.R’ + Running ‘check.R’ + ERROR + Running the tests in ‘tests/check.R’ failed. + Last 50 lines of output: + [[1]][[51]][[1]] + TestResult: + - Test: + - Title: 'value() - visibility' + - Tags: 'value', 'visibility' + ... + - args: function (..., envir = parent.frame()) + - tweaked: FALSE + - call: plan(sequential) + + attr(,"exit_code") + [1] 1 + Total number of errors: 1 + > proc.time() + user system elapsed + 5.376 0.434 14.418 + ``` + # geocmeans
@@ -788,6 +980,31 @@ Run `revdep_details(, "geocmeans")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + |======================================================================| 100%[1] "Calculating the Jaccard values..." + [1] "Extracting the centres of the clusters..." + [1] "Standardizing the data (set parameter to FALSE to avoid this step)" + + | + | | 0% + ... + 8. │ ├─future::resolve(...) + 9. │ └─future:::resolve.list(...) + 10. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) + 11. │ └─future:::signalConditions(...) + 12. │ └─base::stop(condition) + 13. └─future.apply (local) ``(``) + + [ FAIL 1 | WARN 5 | SKIP 0 | PASS 40 ] + Error: Test failures + Execution halted + ``` + * checking installed package size ... NOTE ``` installed size is 14.5Mb @@ -892,6 +1109,45 @@ Run `revdep_details(, "gsynth")` for more info libs 4.9Mb ``` +# gtfs2emis + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/ipeaGIT/gtfs2emis +* Source code: https://github.com/cran/gtfs2emis +* Date/Publication: 2022-11-14 11:30:05 UTC +* Number of recursive dependencies: 96 + +Run `revdep_details(, "gtfs2emis")` for more info + +
+ +## In both + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘gtfs2emis_emission_factor.Rmd’ using rmarkdown + --- finished re-building ‘gtfs2emis_emission_factor.Rmd’ + + --- re-building ‘gtfs2emis_fleet_data.Rmd’ using rmarkdown + --- finished re-building ‘gtfs2emis_fleet_data.Rmd’ + + --- re-building ‘gtfs2emis_intro_vignette.Rmd’ using rmarkdown + Quitting from lines 119-130 (gtfs2emis_intro_vignette.Rmd) + Error: processing vignette 'gtfs2emis_intro_vignette.Rmd' failed with diagnostics: + UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". + --- failed re-building ‘gtfs2emis_intro_vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘gtfs2emis_intro_vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + # gWQS
@@ -1277,6 +1533,67 @@ Run `revdep_details(, "keyATM")` for more info libs 23.6Mb ``` +# lava + +
+ +* Version: 1.7.2.1 +* GitHub: https://github.com/kkholst/lava +* Source code: https://github.com/cran/lava +* Date/Publication: 2023-02-27 08:12:30 UTC +* Number of recursive dependencies: 136 + +Run `revdep_details(, "lava")` for more info + +
+ +## In both + +* checking tests ... + ``` + Running ‘test-all.R’ + ERROR + Running the tests in ‘tests/test-all.R’ failed. + Last 50 lines of output: + > #library("lava") + > suppressPackageStartupMessages(library("testthat")) + > test_check("lava") + Loading required package: lava + + Attaching package: 'lava' + ... + 10. │ ├─future::resolve(...) + 11. │ └─future:::resolve.list(...) + 12. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) + 13. │ └─future:::signalConditions(...) + 14. │ └─base::stop(condition) + 15. └─future.apply (local) ``(``) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 254 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘correlation.Rmd’ using rmarkdown + Quitting from lines 250-253 (correlation.Rmd) + Error: processing vignette 'correlation.Rmd' failed with diagnostics: + UNRELIABLE VALUE: One of the 'future.apply' iterations ('future_lapply-1') unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". + --- failed re-building ‘correlation.Rmd’ + + --- re-building ‘nonlinear.Rmd’ using rmarkdown + --- finished re-building ‘nonlinear.Rmd’ + + SUMMARY: processing the following file failed: + ‘correlation.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + # lidR
@@ -1320,27 +1637,23 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’ + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 37779 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + ERROR Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - 3. └─lidR (local) algorithm(st_bbox(las)) - 4. └─lidR:::crop_special_its(treetops, chm, bbox) - 5. └─lidR:::raster_crop(chm, bbox) - 6. ├─sf::st_crop(raster, bbox) - 7. └─stars:::st_crop.stars(raster, bbox) - ── Error ('test-segment_trees.R:147'): Silva algorithm works with sfc ────────── - ... - 7. └─lidR:::segment_trees.LAS(las, silva2016(chm, ttops_shifted500)) - 8. └─lidR (local) algorithm(st_bbox(las)) - 9. └─lidR:::crop_special_its(treetops, chm, bbox) - 10. └─lidR:::raster_crop(chm, bbox) - 11. ├─sf::st_crop(raster, bbox) - 12. └─stars:::st_crop.stars(raster, bbox) - - [ FAIL 20 | WARN 3 | SKIP 40 | PASS 1357 ] - Error: Test failures - Execution halted + Complete output: + > Sys.setenv("R_TESTS" = "") + > + > library(testthat) + > library(lidR) + > test_check("lidR") + Tests using raster: terra + Tests using future: TRUE + Tests using OpenMP thread: 32 + OGR: Unsupported geometry type + OGR: Unsupported geometry type + terminate called after throwing an instance of 'std::length_error' + what(): basic_string::_S_create ``` * checking installed package size ... NOTE @@ -1518,7 +1831,7 @@ Run `revdep_details(, "MineICA")` for more info > mart <- useMart(biomart = "ensembl", dataset = "hsapiens_gene_ensembl") When sourcing ‘MineICA.R’: - Error: Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 120135 out of -1 bytes received + Error: Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 365789 out of -1 bytes received Execution halted ``` @@ -1630,8 +1943,8 @@ Run `revdep_details(, "MineICA")` for more info IQR, mad, sd, var, xtabs ... - Error in curl::curl_fetch_memory(url, handle = handle) : - Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 121525 out of -1 bytes received + Error in { : task 2 failed - "Multiple cache results found. + Please clear your cache by running biomartCacheClear()" --- failed re-building ‘MineICA.Rnw’ @@ -1681,6 +1994,31 @@ Run `revdep_details(, "mistyR")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + Generating paraview using 2 nearest neighbors per unit + + Generating paraview + + Generating paraview + [ FAIL 2 | WARN 74 | SKIP 0 | PASS 168 ] + ... + 27. └─rlang::abort(...) + ── Failure ('test-misty.R:212'): k for cv , n.bags for bagging can be changed and approx works ── + first.run < second.run is not TRUE + + `actual`: FALSE + `expected`: TRUE + + [ FAIL 2 | WARN 74 | SKIP 0 | PASS 168 ] + Error: Test failures + Execution halted + ``` + * checking R code for possible problems ... NOTE ``` aggregate_results: no visible binding for global variable ‘.data’ @@ -1808,6 +2146,48 @@ Run `revdep_details(, "OOS")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(OOS) + > + > test_check("OOS") + Error : UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". + Error : UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". + ... + Backtrace: + ▆ + 1. ├─testthat::expect_true(...) at test-forecast_multivariate.R:76:2 + 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. └─base::is.data.frame(forecast.multi$forecasts) + + [ FAIL 3 | WARN 1004 | SKIP 0 | PASS 26 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘basic_introduction.Rmd’ using rmarkdown + Quitting from lines 68-78 (basic_introduction.Rmd) + Error: processing vignette 'basic_introduction.Rmd' failed with diagnostics: + UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". + --- failed re-building ‘basic_introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘basic_introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + * checking LazyData ... NOTE ``` 'LazyData' is specified without a 'data' directory @@ -1907,6 +2287,45 @@ Run `revdep_details(, "phylolm")` for more info Packages unavailable to check Rd xrefs: ‘geiger’, ‘caper’ ``` +# PINstimation + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/monty-se/PINstimation +* Source code: https://github.com/cran/PINstimation +* Date/Publication: 2022-10-18 22:58:01 UTC +* Number of recursive dependencies: 65 + +Run `revdep_details(, "PINstimation")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘PINstimation.rmd’ using rmarkdown + Quitting from lines 255-256 (PINstimation.rmd) + Error: processing vignette 'PINstimation.rmd' failed with diagnostics: + Future () added variables to the global environment. A future expression should never assign variables to the global environment - neither by assign() nor by <<-: [n=1] '.lwbound' + --- failed re-building ‘PINstimation.rmd’ + + --- re-building ‘parallel_processing.rmd’ using rmarkdown + Quitting from lines 81-84 (parallel_processing.rmd) + Error: processing vignette 'parallel_processing.rmd' failed with diagnostics: + Future () added variables to the global environment. A future expression should never assign variables to the global environment - neither by assign() nor by <<-: [n=1] '.lwbound' + --- failed re-building ‘parallel_processing.rmd’ + + SUMMARY: processing the following files failed: + ‘PINstimation.rmd’ ‘parallel_processing.rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + # PLNmodels
@@ -2024,6 +2443,23 @@ Run `revdep_details(, "prewas")` for more info ## In both +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘getting_started_with_prewas.Rmd’ using rmarkdown + Quitting from lines 136-141 (getting_started_with_prewas.Rmd) + Error: processing vignette 'getting_started_with_prewas.Rmd' failed with diagnostics: + UNRELIABLE VALUE: One of the 'future.apply' iterations ('future_apply-1') unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". + --- failed re-building ‘getting_started_with_prewas.Rmd’ + + SUMMARY: processing the following file failed: + ‘getting_started_with_prewas.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + * checking dependencies in R code ... NOTE ``` Namespace in Imports field not imported from: ‘stats’ @@ -2158,6 +2594,47 @@ Run `revdep_details(, "regmedint")` for more info All declared Imports should be used. ``` +# reproducible + +
+ +* Version: 1.2.16 +* GitHub: https://github.com/PredictiveEcology/reproducible +* Source code: https://github.com/cran/reproducible +* Date/Publication: 2022-12-22 09:50:02 UTC +* Number of recursive dependencies: 104 + +Run `revdep_details(, "reproducible")` for more info + +
+ +## In both + +* checking tests ... + ``` + Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 72596 Segmentation fault ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + + ERROR + Running the tests in ‘tests/test-all.R’ failed. + Last 50 lines of output: + adding: scratch/henrik/1184987/Rtmpoj91ji/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) + adding: scratch/henrik/1184987/Rtmpoj91ji/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) + + *** caught segfault *** + address 0x40, cause 'memory not mapped' + ... + 36: doTryCatch(return(expr), name, parentenv, handler) + 37: tryCatchOne(expr, names, parentenv, handlers[[1L]]) + 38: tryCatchList(expr, classes, parentenv, handlers) + 39: tryCatch(code, testthat_abort_reporter = function(cnd) { cat(conditionMessage(cnd), "\n") NULL}) + 40: with_reporter(reporters$multi, lapply(test_paths, test_one_file, env = env, wrap = wrap)) + 41: test_files_serial(test_dir = test_dir, test_package = test_package, test_paths = test_paths, load_helpers = load_helpers, reporter = reporter, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package) + 42: test_files(test_dir = path, test_paths = test_paths, test_package = package, reporter = reporter, load_helpers = load_helpers, env = env, stop_on_failure = stop_on_failure, stop_on_warning = stop_on_warning, wrap = wrap, load_package = load_package, parallel = parallel) + 43: test_dir("testthat", package = package, reporter = reporter, ..., load_package = "installed") + 44: test_check("reproducible") + An irrecoverable exception occurred. R is aborting now ... + ``` + # rgee
@@ -2334,6 +2811,47 @@ Run `revdep_details(, "sdmTMB")` for more info Package unavailable to check Rd xrefs: ‘INLA’ ``` +# semtree + +
+ +* Version: 0.9.18 +* GitHub: NA +* Source code: https://github.com/cran/semtree +* Date/Publication: 2022-05-13 20:20:02 UTC +* Number of recursive dependencies: 105 + +Run `revdep_details(, "semtree")` for more info + +
+ +## Newly broken + +* checking tests ... + ``` + Running ‘invariance.R’ + Running ‘lavaan.R’ + Running ‘tree.R’ + Running ‘vim.R’ + ERROR + Running the tests in ‘tests/vim.R’ failed. + Last 50 lines of output: + + to=manifests, + + arrows=1, + + free=FALSE, + ... + Start values from best fit: + 0.0517425665515153,0.0579964396186258,0.0467583826565627,0.0520836944320659,0.0361130740992484,2.41004055880336,0.477157334656551,0.973042342886596,3.49639424861343,-0.465977367752192 + ✖ Variable noise is numeric but has only few unique values. Consider recoding as ordered factor. + ✔ Tree construction finished [took 6s]. + ✖ Variable noise is numeric but has only few unique values. Consider recoding as ordered factor. + ✔ Tree construction finished [took 6s]. + ✖ Variable noise is numeric but has only few unique values. Consider recoding as ordered factor. + ✔ Tree construction finished [took 5s]. + Error: Future (future_mapply-1) added variables to the global environment. A future expression should never assign variables to the global environment - neither by assign() nor by <<-: [n=1] 'global.node.id' + Execution halted + ``` + # sentopics
@@ -2562,6 +3080,45 @@ Run `revdep_details(, "SimDesign")` for more info doc 6.2Mb ``` +# simhelpers + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/meghapsimatrix/simhelpers +* Source code: https://github.com/cran/simhelpers +* Date/Publication: 2022-05-03 22:40:02 UTC +* Number of recursive dependencies: 103 + +Run `revdep_details(, "simhelpers")` for more info + +
+ +## In both + +* checking examples ... ERROR + ``` + Running examples in ‘simhelpers-Ex.R’ failed + The error most likely occurred in: + + > ### Name: evaluate_by_row + > ### Title: Evaluate a simulation function on each row of a data frame or + > ### tibble + > ### Aliases: evaluate_by_row + > + > ### ** Examples + > + > df <- data.frame( + + n = 3:5, + + lambda = seq(8, 16, 4) + + ) + > + > evaluate_by_row(df, rpois) + Error: UNRELIABLE VALUE: Future (‘’) unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". + Timing stopped at: 0.227 0.035 0.614 + Execution halted + ``` + # skpr
@@ -2612,11 +3169,11 @@ Run `revdep_details(, "solitude")` for more info
-* Version: 4.1.20 +* Version: 4.2.1 * GitHub: NA * Source code: https://github.com/cran/spaMM -* Date/Publication: 2022-12-12 12:50:03 UTC -* Number of recursive dependencies: 122 +* Date/Publication: 2023-03-03 15:20:02 UTC +* Number of recursive dependencies: 119 Run `revdep_details(, "spaMM")` for more info @@ -2635,9 +3192,9 @@ Run `revdep_details(, "spaMM")` for more info * checking installed package size ... NOTE ``` - installed size is 55.5Mb + installed size is 55.7Mb sub-directories of 1Mb or more: - R 2.5Mb + R 2.6Mb libs 51.8Mb ``` @@ -2680,6 +3237,56 @@ Run `revdep_details(, "SPARSEMODr")` for more info ## In both +* checking examples ... ERROR + ``` + Running examples in ‘SPARSEMODr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: model_parallel + > ### Title: Parallelized implementation of the SPARSE-MOD models + > ### Aliases: model_parallel + > + > ### ** Examples + > + > ## See vignettes for more detailed work-ups. + ... + Parameter input_R_pops was not specified; assuming to be zeroes. + Parameter input_D_pops was not specified; assuming to be zeroes. + > + > covid_model_output <- + + get_result( + + input_realz_seeds = realz_seeds, + + control = covid19_control + + ) + Error: UNRELIABLE VALUE: One of the ‘future.apply’ iterations (‘future_lapply-1’) unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". + Execution halted + ``` + +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > if(require(testthat))test_check("SPARSEMODr") + Loading required package: testthat + Loading required package: SPARSEMODr + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 13. │ ├─future::resolve(...) + 14. │ └─future:::resolve.list(...) + 15. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) + 16. │ └─future:::signalConditions(...) + 17. │ └─base::stop(condition) + 18. └─future.apply (local) ``(``) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + * checking dependencies in R code ... NOTE ``` Namespaces in Imports field not imported from: @@ -2785,6 +3392,31 @@ Run `revdep_details(, "spNetwork")` for more info ## In both +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + 5. │ ├─base::withCallingHandlers(...) + 6. │ └─(function() {... + 7. │ ├─future::value(fs) + 8. │ └─future:::value.list(fs) + 9. │ ├─future::resolve(...) + 10. │ └─future:::resolve.list(...) + ... + 9. │ ├─future::resolve(...) + 10. │ └─future:::resolve.list(...) + 11. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) + 12. │ └─future:::signalConditions(...) + 13. │ └─base::stop(condition) + 14. └─future.apply (local) ``(``) + + [ FAIL 5 | WARN 3 | SKIP 0 | PASS 68 ] + Error: Test failures + Execution halted + ``` + * checking installed package size ... NOTE ``` installed size is 25.2Mb From 6cd94e7fb3d556d0205ba95045b700b8caeb6981 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 6 Mar 2023 13:15:56 +0100 Subject: [PATCH 85/88] NEWS: tweaks --- NEWS.md | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/NEWS.md b/NEWS.md index e63460b8..355b638d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,9 +1,13 @@ -# Version 1.312.0 [2023-03-03] +# Version 1.32.0 [2023-03-06] ## New Features - * Added optional assertion against adding variables to the global - environment by a future. + * Add prototype of an internal event-logging framework for the + purpose of profiling futures and their backends. + + * Add option `future.globalenv.onMisuse` for optionally assert that a + future expression does not result in variables being added to the + global environment. * Add option `future.onFutureCondition.keepFuture` for controlling whether `FutureCondition` objects should keep a copy of the @@ -12,9 +16,6 @@ will also be large, which can result in memory issues and slow downs. - * Add prototype of an internal event-logging framework for the - purpose of profiling futures and their backends. - ## Miscellaneous * Fix a **future.tests** check that occurred only on MS Windows. From 3e1ae16b6665803102870e2b81f9ee5d58ef5219 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 6 Mar 2023 09:55:00 -0800 Subject: [PATCH 86/88] REVDEP: 280 revdep packages with 'multiprocess' being defunct; there are four packages failing as expected [ci skip] [#546] --- R/options.R | 2 +- revdep/README.md | 581 ++++++++++++++++--------------- revdep/cran.md | 15 +- revdep/problems.md | 807 ++++++++++--------------------------------- tests/multiprocess.R | 149 -------- 5 files changed, 488 insertions(+), 1066 deletions(-) delete mode 100644 tests/multiprocess.R diff --git a/R/options.R b/R/options.R index 393f08dc..b3f8642e 100644 --- a/R/options.R +++ b/R/options.R @@ -274,7 +274,7 @@ update_package_options <- function(debug = FALSE) { update_package_option("future.deprecated.ignore", split = ",", debug = debug) - update_package_option("future.deprecated.defunct", mode = "character", split = ",", default = if (interactive()) "multiprocess" else NULL, debug = debug) + update_package_option("future.deprecated.defunct", mode = "character", split = ",", default = "multiprocess", debug = debug) update_package_option("future.fork.multithreading.enable", mode = "logical", debug = debug) diff --git a/revdep/README.md b/revdep/README.md index 6683bf7c..51ae9e10 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,7 +10,7 @@ |collate |en_US.UTF-8 | |ctype |en_US.UTF-8 | |tz |America/Los_Angeles | -|date |2023-03-04 | +|date |2023-03-06 | |pandoc |3.0.1 @ /software/c4/cbi/software/pandoc-3.0.1/bin/pandoc | # Dependencies @@ -26,298 +26,297 @@ # Revdeps -## New problems (5) +## New problems (4) -|package |version |error |warning |note | -|:------------|:-------|:------|:-------|:----| -|[alookr](problems.md#alookr)|0.3.7 |__+1__ | | | -|[civis](problems.md#civis)|3.1.1 |__+1__ | | | -|[future.tests](problems.md#futuretests)|0.5.0 |__+1__ | | | -|[PINstimation](problems.md#pinstimation)|0.1.1 |__+1__ | | | -|[semtree](problems.md#semtree)|0.9.18 |__+1__ | | | +|package |version |error |warning |note | +|:-------|:-------|:--------|:-------|:----| +|[dhReg](problems.md#dhreg)|0.1.1 |__+1__ | | | +|[fiery](problems.md#fiery)|1.1.4 |__+1__ | | | +|[MineICA](problems.md#mineica)|1.38.0 |1 __+1__ |3 |4 | +|[prewas](problems.md#prewas)|1.1.1 |__+2__ | |1 | ## All (280) -|package |version |error |warning |note | -|:------------------------|:---------|:------|:-------|:----| -|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | -|[alookr](problems.md#alookr)|0.3.7 |__+1__ | | | -|alphaci |1.0.0 | | | | -|[AlpsNMR](problems.md#alpsnmr)|4.0.4 |1 | | | -|arkdb |0.0.16 | | | | -|aroma.affymetrix |3.2.1 | | | | -|aroma.cn |1.7.0 | | | | -|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | -|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | -|bamm |0.4.3 | | | | -|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | -|BatchGetSymbols |2.6.4 | | | | -|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | -|bayesian |0.0.9 | | | | -|bayesmove |0.2.1 | | | | -|bcmaps |1.1.0 | | | | -|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | -|bhmbasket |0.9.5 | | | | -|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | -|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | -|bkmrhat |1.1.3 | | | | -|[blavaan](problems.md#blavaan)|0.4-7 | | |3 | -|bolasso |0.2.0 | | | | -|[brms](problems.md#brms) |2.18.0 | | |2 | -|brpop |0.1.5 | | | | -|canaper |1.0.0 | | | | -|ceRNAnetsim |1.10.0 | | | | -|cft |1.0.0 | | | | -|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | -|[civis](problems.md#civis)|3.1.1 |__+1__ | | | -|Clustering |1.7.7 | | | | -|codalm |0.1.2 | | | | -|[codebook](problems.md#codebook)|0.9.2 |1 | |3 | -|conformalInference.fd |1.1.1 | | | | -|conformalInference.multi |1.1.1 | | | | -|crossmap |0.4.0 | | | | -|CSCNet |0.1.2 | | | | -|[cSEM](problems.md#csem) |0.5.0 |1 | |1 | -|[CSGo](problems.md#csgo) |0.6.7 | | |1 | -|cvCovEst |1.2.0 | | | | -|dagHMM |0.1.0 | | | | -|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | -|delayed |0.4.0 | | | | -|dhReg |0.1.1 | | | | -|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | -|disk.frame |0.8.0 | | | | -|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | -|doFuture |0.12.2 | | | | -|DQAstats |0.3.2 | | | | -|[dragon](problems.md#dragon)|1.2.1 | | |1 | -|drake |7.13.4 | | | | -|drimmR |1.0.1 | | | | -|drtmle |1.1.2 | | | | -|dsos |0.1.2 | | | | -|DT |0.27 | | | | -|easyalluvial |0.3.1 | | | | -|ecic |0.0.3 | | | | -|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | -|elevatr |0.4.2 | | | | -|[envi](problems.md#envi) |0.1.17 | |1 | | -|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | -|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | -|epwshiftr |0.1.3 | | | | -|ezcox |1.0.2 | | | | -|fabletools |0.3.2 | | | | -|FAMoS |0.3.0 | | | | -|fastRhockey |0.4.0 | | | | -|[fect](problems.md#fect) |1.0.0 | | |2 | -|fiery |1.1.4 | | | | -|finbif |0.7.2 | | | | -|fitlandr |0.1.0 | | | | -|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | -|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | -|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | -|fst4pg |1.0.0 | | | | -|fundiversity |1.1.1 | | | | -|funGp |0.3.1 | | | | -|furrr |0.3.1 | | | | -|future.apply |1.10.0 | | | | -|future.batchtools |0.12.0 | | | | -|future.callr |0.8.1 | | | | -|[future.tests](problems.md#futuretests)|0.5.0 |__+1__ | | | -|fxTWAPLS |0.1.2 | | | | -|genBaRcode |1.2.5 | | | | -|[geocmeans](problems.md#geocmeans)|0.3.3 |1 | |1 | -|GetBCBData |0.7.0 | | | | -|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | -|googlePubsubR |0.0.4 | | | | -|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | -|[greed](problems.md#greed)|0.6.1 | | |2 | -|greta |0.4.3 | | | | -|gstat |2.1-0 | | | | -|GSVA |1.46.0 | | | | -|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | -|[gtfs2emis](problems.md#gtfs2emis)|0.1.0 |1 | | | -|gtfs2gps |2.1-0 | | | | -|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | -|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | -|hacksig |0.1.2 | | | | -|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | -|haldensify |0.2.3 | | | | -|hoopR |1.8.0 | | | | -|[hwep](problems.md#hwep) |2.0.0 | | |2 | -|idmodelr |0.4.0 | | | | -|imagefluency |0.2.4 | | | | -|iml |0.11.1 | | | | -|incubate |1.2.0 | | | | -|[infercnv](problems.md#infercnv)|1.14.1 | |1 |3 | -|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | -|[InPAS](problems.md#inpas)|2.6.0 | | |1 | -|[interflex](problems.md#interflex)|1.2.6 | | |1 | -|ipc |0.1.4 | | | | -|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | -|isopam |1.1.0 | | | | -|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | -|JointAI |1.0.4 | | | | -|jstor |0.3.10 | | | | -|JuliaConnectoR |1.1.1 | | | | -|kernelboot |0.1.9 | | | | -|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | -|latentcor |2.0.1 | | | | -|[lava](problems.md#lava) |1.7.2.1 |2 | | | -|ldaPrototype |0.3.1 | | | | -|ldsr |0.0.2 | | | | -|lemna |1.0.0 | | | | -|LexFindR |1.0.2 | | | | -|lgr |0.4.4 | | | | -|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | -|[lightr](problems.md#lightr)|1.7.0 | | |2 | -|lmtp |1.3.1 | | | | -|LWFBrook90R |0.5.2 | | | | -|[MAI](problems.md#mai) |1.4.0 | | |1 | -|MAMS |2.0.0 | | | | -|marginaleffects |0.10.0 | | | | -|mcmcensemble |3.0.0 | | | | -|mcp |0.3.2 | | | | -|merTools |0.5.2 | | | | -|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | -|[mice](problems.md#mice) |3.15.0 | |1 | | -|[microservices](problems.md#microservices)|0.2.0 |1 | | | -|microSTASIS |0.1.0 | | | | -|migraph |0.13.2 | | | | -|mikropml |1.5.0 | | | | -|[MineICA](problems.md#mineica)|1.38.0 |1 |3 |4 | -|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | -|[mistyR](problems.md#mistyr)|1.6.1 |1 | |1 | -|mlr3 |0.14.1 | | | | -|mlr3db |0.5.0 | | | | -|mlr3pipelines |0.4.2 | | | | -|mlr3spatial |0.4.0 | | | | -|modelsummary |1.3.0 | | | | -|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | -|MOSS |0.2.2 | | | | -|mrgsim.parallel |0.2.1 | | | | -|[mslp](problems.md#mslp) |1.0.1 |1 | | | -|multiverse |0.6.1 | | | | -|netShiny |1.0 | | | | -|NetSimR |0.1.2 | | | | -|nfl4th |1.0.2 | | | | -|nflfastR |4.5.1 | | | | -|nflseedR |1.2.0 | | | | -|nncc |1.0.0 | | | | -|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | -|onemapsgapi |1.1.0 | | | | -|[OOS](problems.md#oos) |1.0.0 |2 | |1 | -|origami |1.0.7 | | | | -|paramsim |0.1.0 | | | | -|[partR2](problems.md#partr2)|0.9.1 | | |1 | -|[pavo](problems.md#pavo) |2.8.0 | |1 | | -|pbapply |1.7-0 | | | | -|PCRedux |1.1-2 | | | | -|PeakSegDisk |2022.2.1 | | | | -|penaltyLearning |2020.5.13 | | | | -|pGRN |0.3.5 | | | | -|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | -|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | -|[PINstimation](problems.md#pinstimation)|0.1.1 |__+1__ | | | -|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | -|plumber |1.2.1 | | | | -|polle |1.2 | | | | -|POMADE |0.1.0 | | | | -|[portvine](problems.md#portvine)|1.0.2 | | |1 | -|powRICLPM |0.1.1 | | | | -|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | -|[prewas](problems.md#prewas)|1.1.1 |1 | |1 | -|progressr |0.13.0 | | | | -|[projpred](problems.md#projpred)|2.4.0 | | |1 | -|[promises](problems.md#promises)|1.2.0.1 | | |1 | -|Prostar |1.30.7 | | | | -|protti |0.6.0 | | | | -|PSCBS |0.66.0 | | | | -|PUMP |1.0.1 | | | | -|qape |2.0 | | | | -|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | -|qgcomp |2.10.1 | | | | -|qgcompint |0.7.0 | | | | -|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | -|rangeMapper |2.0.3 | | | | -|rBiasCorrection |0.3.4 | | | | -|receptiviti |0.1.3 | | | | -|refineR |1.5.1 | | | | -|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | -|remiod |1.0.2 | | | | -|[reproducible](problems.md#reproducible)|1.2.16 |1 | | | -|reval |3.1-0 | | | | -|[rgee](problems.md#rgee) |1.1.5 | | |2 | -|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | -|robust2sls |0.2.2 | | | | -|RTransferEntropy |0.2.21 | | | | -|s3fs |0.1.3 | | | | -|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | -|scBubbletree |1.0.0 | | | | -|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | -|SCtools |0.3.2.1 | | | | -|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | -|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | -|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | -|seer |1.1.8 | | | | -|[semtree](problems.md#semtree)|0.9.18 |__+1__ | | | -|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | -|[Seurat](problems.md#seurat)|4.3.0 | | |2 | -|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | -|[shiny](problems.md#shiny)|1.7.4 | | |1 | -|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | -|sigminer |2.1.9 | | | | -|Signac |1.9.0 | | | | -|[signeR](problems.md#signer)|2.0.2 | | |3 | -|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | -|simfinapi |0.2.3 | | | | -|simglm |0.8.9 | | | | -|[simhelpers](problems.md#simhelpers)|0.1.2 |1 | | | -|sims |0.0.3 | | | | -|skewlmm |1.0.0 | | | | -|[skpr](problems.md#skpr) |1.1.6 | | |1 | -|smoots |1.1.3 | | | | -|sNPLS |1.0.27 | | | | -|[solitude](problems.md#solitude)|1.1.3 | | |1 | -|sovereign |1.2.1 | | | | -|[spaMM](problems.md#spamm)|4.2.1 | | |2 | -|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | -|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 |2 | |1 | -|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | -|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | -|specr |1.0.0 | | | | -|sperrorest |3.0.5 | | | | -|spFSR |2.0.3 | | | | -|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | -|[spNetwork](problems.md#spnetwork)|0.4.3.6 |1 | |1 | -|[squat](problems.md#squat)|0.1.0 | | |1 | -|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | -|[stars](problems.md#stars)|0.6-0 | | |2 | -|startR |2.2.1 | | | | -|steps |1.3.0 | | | | -|supercells |0.9.1 | | | | -|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | -|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | -|tarchetypes |0.7.4 | | | | -|[targeted](problems.md#targeted)|0.3 | | |1 | -|targets |0.14.2 | | | | -|tcplfit2 |0.1.3 | | | | -|tealeaves |1.0.6 | | | | -|templr |0.2-0 | | | | -|[text](problems.md#text) |0.9.99.2 | | |1 | -|tglkmeans |0.3.5 | | | | -|tidyqwi |0.1.2 | | | | -|TKCat |1.0.7 | | | | -|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | -|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | -|tsfeatures |1.1 | | | | -|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | -|[txshift](problems.md#txshift)|0.3.8 | | |1 | -|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.10 | | |1 | -|[updog](problems.md#updog)|2.1.3 | | |1 | -|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | -|webdeveloper |1.0.5 | | | | -|whitewater |0.1.2 | | | | -|wildmeta |0.3.1 | | | | -|[wru](problems.md#wru) |1.0.1 | | |2 | -|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | -|yfR |1.1.0 | | | | +|package |version |error |warning |note | +|:------------------------|:---------|:--------|:-------|:----| +|[AIPW](problems.md#aipw) |0.6.3.2 | | |1 | +|alookr |0.3.7 | | | | +|alphaci |1.0.0 | | | | +|AlpsNMR |4.0.4 | | | | +|arkdb |0.0.16 | | | | +|aroma.affymetrix |3.2.1 | | | | +|aroma.cn |1.7.0 | | | | +|[aroma.core](problems.md#aromacore)|3.3.0 | | |1 | +|[BAMBI](problems.md#bambi)|2.3.4 | | |1 | +|bamm |0.4.3 | | | | +|[baseballr](problems.md#baseballr)|1.3.0 |1 | | | +|BatchGetSymbols |2.6.4 | | | | +|[batchtools](problems.md#batchtools)|0.9.16 | | |2 | +|bayesian |0.0.9 | | | | +|bayesmove |0.2.1 | | | | +|bcmaps |1.1.0 | | | | +|[BEKKs](problems.md#bekks)|1.4.1 | | |2 | +|bhmbasket |0.9.5 | | | | +|[bigDM](problems.md#bigdm)|0.5.1 | | |2 | +|[bistablehistory](problems.md#bistablehistory)|1.1.1 | | |3 | +|bkmrhat |1.1.3 | | | | +|[blavaan](problems.md#blavaan)|0.4-7 | | |3 | +|bolasso |0.2.0 | | | | +|[brms](problems.md#brms) |2.18.0 | | |2 | +|brpop |0.1.5 | | | | +|canaper |1.0.0 | | | | +|ceRNAnetsim |1.10.0 | | | | +|cft |1.0.0 | | | | +|[ChromSCape](problems.md#chromscape)|1.8.0 | | |4 | +|civis |3.1.1 | | | | +|Clustering |1.7.7 | | | | +|codalm |0.1.2 | | | | +|[codebook](problems.md#codebook)|0.9.2 | | |3 | +|conformalInference.fd |1.1.1 | | | | +|conformalInference.multi |1.1.1 | | | | +|crossmap |0.4.0 | | | | +|CSCNet |0.1.2 | | | | +|[cSEM](problems.md#csem) |0.5.0 | | |1 | +|[CSGo](problems.md#csgo) |0.6.7 | | |1 | +|cvCovEst |1.2.0 | | | | +|dagHMM |0.1.0 | | | | +|[DeclareDesign](problems.md#declaredesign)|1.0.2 | | |1 | +|delayed |0.4.0 | | | | +|[dhReg](problems.md#dhreg)|0.1.1 |__+1__ | | | +|[dipsaus](problems.md#dipsaus)|0.2.6 | | |1 | +|disk.frame |0.8.0 | | | | +|[dispositionEffect](problems.md#dispositioneffect)|1.0.1 |1 | | | +|doFuture |0.12.2 | | | | +|DQAstats |0.3.2 | | | | +|[dragon](problems.md#dragon)|1.2.1 | | |1 | +|drake |7.13.4 | | | | +|drimmR |1.0.1 | | | | +|drtmle |1.1.2 | | | | +|dsos |0.1.2 | | | | +|DT |0.27 | | | | +|easyalluvial |0.3.1 | | | | +|ecic |0.0.3 | | | | +|[EFAtools](problems.md#efatools)|0.4.4 | | |2 | +|elevatr |0.4.2 | | | | +|[envi](problems.md#envi) |0.1.17 | |1 | | +|[EpiNow2](problems.md#epinow2)|1.3.4 | | |2 | +|[epitweetr](problems.md#epitweetr)|2.2.13 | | |2 | +|epwshiftr |0.1.3 | | | | +|ezcox |1.0.2 | | | | +|fabletools |0.3.2 | | | | +|FAMoS |0.3.0 | | | | +|fastRhockey |0.4.0 | | | | +|[fect](problems.md#fect) |1.0.0 | | |2 | +|[fiery](problems.md#fiery)|1.1.4 |__+1__ | | | +|finbif |0.7.2 | | | | +|fitlandr |0.1.0 | | | | +|[flowGraph](problems.md#flowgraph)|1.6.0 | | |2 | +|[foieGras](problems.md#foiegras)|0.7-6 | | |1 | +|[forecastML](problems.md#forecastml)|0.9.0 | | |1 | +|fst4pg |1.0.0 | | | | +|fundiversity |1.1.1 | | | | +|funGp |0.3.1 | | | | +|furrr |0.3.1 | | | | +|future.apply |1.10.0 | | | | +|future.batchtools |0.12.0 | | | | +|future.callr |0.8.1 | | | | +|future.tests |0.5.0 | | | | +|fxTWAPLS |0.1.2 | | | | +|genBaRcode |1.2.5 | | | | +|[geocmeans](problems.md#geocmeans)|0.3.3 | | |1 | +|GetBCBData |0.7.0 | | | | +|[googleComputeEngineR](problems.md#googlecomputeenginer)|0.3.0 | | |1 | +|googlePubsubR |0.0.4 | | | | +|[googleTagManageR](problems.md#googletagmanager)|0.2.0 | | |1 | +|[greed](problems.md#greed)|0.6.1 | | |2 | +|greta |0.4.3 | | | | +|gstat |2.1-0 | | | | +|GSVA |1.46.0 | | | | +|[gsynth](problems.md#gsynth)|1.2.1 | | |1 | +|gtfs2emis |0.1.0 | | | | +|gtfs2gps |2.1-0 | | | | +|[gWQS](problems.md#gwqs) |3.0.4 | | |1 | +|[hackeRnews](problems.md#hackernews)|0.1.0 | | |1 | +|hacksig |0.1.2 | | | | +|[hal9001](problems.md#hal9001)|0.4.3 | | |1 | +|haldensify |0.2.3 | | | | +|hoopR |1.8.0 | | | | +|[hwep](problems.md#hwep) |2.0.0 | | |2 | +|idmodelr |0.4.0 | | | | +|imagefluency |0.2.4 | | | | +|iml |0.11.1 | | | | +|incubate |1.2.0 | | | | +|[infercnv](problems.md#infercnv)|1.14.1 | |1 |3 | +|[inlinedocs](problems.md#inlinedocs)|2019.12.5 | | |1 | +|[InPAS](problems.md#inpas)|2.6.0 | | |1 | +|[interflex](problems.md#interflex)|1.2.6 | | |1 | +|ipc |0.1.4 | | | | +|[ISAnalytics](problems.md#isanalytics)|1.8.1 |3 | |2 | +|isopam |1.1.0 | | | | +|[ivmte](problems.md#ivmte)|1.4.0 | | |1 | +|JointAI |1.0.4 | | | | +|jstor |0.3.10 | | | | +|JuliaConnectoR |1.1.1 | | | | +|kernelboot |0.1.9 | | | | +|[keyATM](problems.md#keyatm)|0.4.2 | | |1 | +|latentcor |2.0.1 | | | | +|lava |1.7.2.1 | | | | +|ldaPrototype |0.3.1 | | | | +|ldsr |0.0.2 | | | | +|lemna |1.0.0 | | | | +|LexFindR |1.0.2 | | | | +|lgr |0.4.4 | | | | +|[lidR](problems.md#lidr) |4.0.2 |2 | |1 | +|[lightr](problems.md#lightr)|1.7.0 | | |2 | +|lmtp |1.3.1 | | | | +|LWFBrook90R |0.5.2 | | | | +|[MAI](problems.md#mai) |1.4.0 | | |1 | +|MAMS |2.0.0 | | | | +|marginaleffects |0.10.0 | | | | +|mcmcensemble |3.0.0 | | | | +|mcp |0.3.2 | | | | +|merTools |0.5.2 | | | | +|[metabolomicsR](problems.md#metabolomicsr)|1.0.0 | | |1 | +|[mice](problems.md#mice) |3.15.0 | |1 | | +|[microservices](problems.md#microservices)|0.2.0 |1 | | | +|microSTASIS |0.1.0 | | | | +|migraph |0.13.2 | | | | +|mikropml |1.5.0 | | | | +|[MineICA](problems.md#mineica)|1.38.0 |1 __+1__ |3 |4 | +|[missSBM](problems.md#misssbm)|1.0.3 | | |1 | +|[mistyR](problems.md#mistyr)|1.6.1 | | |1 | +|mlr3 |0.14.1 | | | | +|mlr3db |0.5.0 | | | | +|mlr3pipelines |0.4.2 | | | | +|mlr3spatial |0.4.0 | | | | +|modelsummary |1.3.0 | | | | +|[momentuHMM](problems.md#momentuhmm)|1.5.5 | | |1 | +|MOSS |0.2.2 | | | | +|mrgsim.parallel |0.2.1 | | | | +|[mslp](problems.md#mslp) |1.0.1 |1 | | | +|multiverse |0.6.1 | | | | +|netShiny |1.0 | | | | +|NetSimR |0.1.2 | | | | +|nfl4th |1.0.2 | | | | +|nflfastR |4.5.1 | | | | +|nflseedR |1.2.0 | | | | +|nncc |1.0.0 | | | | +|[oncomsm](problems.md#oncomsm)|0.1.2 | | |2 | +|onemapsgapi |1.1.0 | | | | +|[OOS](problems.md#oos) |1.0.0 | | |1 | +|origami |1.0.7 | | | | +|paramsim |0.1.0 | | | | +|[partR2](problems.md#partr2)|0.9.1 | | |1 | +|[pavo](problems.md#pavo) |2.8.0 | |1 | | +|pbapply |1.7-0 | | | | +|PCRedux |1.1-2 | | | | +|PeakSegDisk |2022.2.1 | | | | +|penaltyLearning |2020.5.13 | | | | +|pGRN |0.3.5 | | | | +|[photosynthesis](problems.md#photosynthesis)|2.1.1 | | |2 | +|[phylolm](problems.md#phylolm)|2.6.2 | | |1 | +|PINstimation |0.1.1 | | | | +|[PLNmodels](problems.md#plnmodels)|1.0.1 | | |1 | +|plumber |1.2.1 | | | | +|polle |1.2 | | | | +|POMADE |0.1.0 | | | | +|[portvine](problems.md#portvine)|1.0.2 | | |1 | +|powRICLPM |0.1.1 | | | | +|[ppcseq](problems.md#ppcseq)|1.6.0 | | |3 | +|[prewas](problems.md#prewas)|1.1.1 |__+2__ | |1 | +|progressr |0.13.0 | | | | +|[projpred](problems.md#projpred)|2.4.0 | | |1 | +|[promises](problems.md#promises)|1.2.0.1 | | |1 | +|Prostar |1.30.7 | | | | +|protti |0.6.0 | | | | +|PSCBS |0.66.0 | | | | +|PUMP |1.0.1 | | | | +|qape |2.0 | | | | +|[QDNAseq](problems.md#qdnaseq)|1.34.0 | | |1 | +|qgcomp |2.10.1 | | | | +|qgcompint |0.7.0 | | | | +|[RAINBOWR](problems.md#rainbowr)|0.1.29 | | |1 | +|[rangeMapper](problems.md#rangemapper)|2.0.3 |1 | | | +|rBiasCorrection |0.3.4 | | | | +|receptiviti |0.1.3 | | | | +|refineR |1.5.1 | | | | +|[regmedint](problems.md#regmedint)|1.0.0 | | |1 | +|remiod |1.0.2 | | | | +|[reproducible](problems.md#reproducible)|1.2.16 |1 | | | +|reval |3.1-0 | | | | +|[rgee](problems.md#rgee) |1.1.5 | | |2 | +|[robotstxt](problems.md#robotstxt)|0.7.13 | | |2 | +|robust2sls |0.2.2 | | | | +|RTransferEntropy |0.2.21 | | | | +|s3fs |0.1.3 | | | | +|[sapfluxnetr](problems.md#sapfluxnetr)|0.1.4 | | |1 | +|scBubbletree |1.0.0 | | | | +|[scDiffCom](problems.md#scdiffcom)|0.1.0 | | |1 | +|SCtools |0.3.2.1 | | | | +|[sctransform](problems.md#sctransform)|0.3.5 | | |1 | +|[sdmApp](problems.md#sdmapp)|0.0.2 | | |1 | +|[sdmTMB](problems.md#sdmtmb)|0.3.0 | | |3 | +|seer |1.1.8 | | | | +|semtree |0.9.18 | | | | +|[sentopics](problems.md#sentopics)|0.7.1 | | |3 | +|[Seurat](problems.md#seurat)|4.3.0 | | |2 | +|[SeuratObject](problems.md#seuratobject)|4.1.3 | | |1 | +|[shiny](problems.md#shiny)|1.7.4 | | |1 | +|[shiny.worker](problems.md#shinyworker)|0.0.1 | | |2 | +|sigminer |2.1.9 | | | | +|Signac |1.9.0 | | | | +|[signeR](problems.md#signer)|2.0.2 | | |3 | +|[SimDesign](problems.md#simdesign)|2.10.1 | | |2 | +|simfinapi |0.2.3 | | | | +|simglm |0.8.9 | | | | +|simhelpers |0.1.2 | | | | +|sims |0.0.3 | | | | +|skewlmm |1.0.0 | | | | +|[skpr](problems.md#skpr) |1.1.6 | | |1 | +|smoots |1.1.3 | | | | +|sNPLS |1.0.27 | | | | +|[solitude](problems.md#solitude)|1.1.3 | | |1 | +|sovereign |1.2.1 | | | | +|[spaMM](problems.md#spamm)|4.2.1 | | |2 | +|[sparrpowR](problems.md#sparrpowr)|0.2.7 | |1 | | +|[SPARSEMODr](problems.md#sparsemodr)|1.2.0 | | |1 | +|[spatialTIME](problems.md#spatialtime)|1.2.2 | | |1 | +|[spatialwarnings](problems.md#spatialwarnings)|3.0.3 | |1 |1 | +|specr |1.0.0 | | | | +|sperrorest |3.0.5 | | | | +|spFSR |2.0.3 | | | | +|[sphunif](problems.md#sphunif)|1.0.1 | | |2 | +|[spNetwork](problems.md#spnetwork)|0.4.3.6 | | |1 | +|[squat](problems.md#squat)|0.1.0 | | |1 | +|[ssdtools](problems.md#ssdtools)|1.0.2 | | |1 | +|[stars](problems.md#stars)|0.6-0 | | |2 | +|startR |2.2.1 | | | | +|steps |1.3.0 | | | | +|supercells |0.9.1 | | | | +|[synergyfinder](problems.md#synergyfinder)|3.6.3 | |1 |2 | +|[tableschema.r](problems.md#tableschemar)|1.1.2 | | |1 | +|tarchetypes |0.7.4 | | | | +|[targeted](problems.md#targeted)|0.3 | | |1 | +|targets |0.14.2 | | | | +|tcplfit2 |0.1.3 | | | | +|tealeaves |1.0.6 | | | | +|templr |0.2-0 | | | | +|[text](problems.md#text) |0.9.99.2 | | |1 | +|tglkmeans |0.3.5 | | | | +|tidyqwi |0.1.2 | | | | +|TKCat |1.0.7 | | | | +|[TreeSearch](problems.md#treesearch)|1.3.0 |1 | |1 | +|[TriDimRegression](problems.md#tridimregression)|1.0.1 | | |3 | +|tsfeatures |1.1 | | | | +|[TSstudio](problems.md#tsstudio)|0.1.6 | | |1 | +|[txshift](problems.md#txshift)|0.3.8 | | |1 | +|[UCSCXenaShiny](problems.md#ucscxenashiny)|1.1.10 | | |1 | +|[updog](problems.md#updog)|2.1.3 | | |1 | +|[vmeasur](problems.md#vmeasur)|0.1.4 | |1 | | +|webdeveloper |1.0.5 | | | | +|whitewater |0.1.2 | | | | +|wildmeta |0.3.1 | | | | +|[wru](problems.md#wru) |1.0.1 | | |2 | +|[XNAString](problems.md#xnastring)|1.6.0 | | |3 | +|yfR |1.1.0 | | | | diff --git a/revdep/cran.md b/revdep/cran.md index 750961ba..8558cabb 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,7 +2,7 @@ We checked 280 reverse dependencies (261 from CRAN + 19 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 5 new problems + * We saw 3 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -10,18 +10,13 @@ Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* alookr - checking examples ... ERROR - -* civis +* dhReg checking tests ... -* future.tests +* fiery checking tests ... -* PINstimation - checking re-building of vignette outputs ... ERROR - -* semtree +* prewas checking tests ... + checking re-building of vignette outputs ... ERROR diff --git a/revdep/problems.md b/revdep/problems.md index 148d75cc..be41feb3 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -22,88 +22,6 @@ Run `revdep_details(, "AIPW")` for more info All declared Imports should be used. ``` -# alookr - -
- -* Version: 0.3.7 -* GitHub: https://github.com/choonghyunryu/alookr -* Source code: https://github.com/cran/alookr -* Date/Publication: 2022-06-12 15:30:02 UTC -* Number of recursive dependencies: 158 - -Run `revdep_details(, "alookr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘alookr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: run_models - > ### Title: Fit binary classification model - > ### Aliases: run_models - > - > ### ** Examples - > - > library(dplyr) - ... - 10. │ ├─purrr:::call_with_cleanup(...) - 11. │ └─alookr (local) .f(.x[[i]], ...) - 12. │ ├─future::value(.x) - 13. │ └─future:::value.Future(.x) - 14. │ └─future:::signalConditions(...) - 15. │ └─base::stop(condition) - 16. └─purrr (local) ``(``) - 17. └─cli::cli_abort(...) - 18. └─rlang::abort(...) - Execution halted - ``` - -# AlpsNMR - -
- -* Version: 4.0.4 -* GitHub: https://github.com/sipss/AlpsNMR -* Source code: https://github.com/cran/AlpsNMR -* Date/Publication: 2023-02-16 -* Number of recursive dependencies: 169 - -Run `revdep_details(, "AlpsNMR")` for more info - -
- -## In both - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘Vig01-introduction-to-alpsnmr.Rmd’ using rmarkdown - Warning in has_utility("pdfcrop") : - pdfcrop not installed or not in PATH - sh: pdfcrop: command not found - Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : - error in running command - sh: pdfcrop: command not found - Warning in system2("pdfcrop", shQuote(c(x, x)), stdout = if (quiet) FALSE else "") : - error in running command - ... - Warning: (fancyhdr) \setlength{\headheight}{46.27916pt}. - Warning: (fancyhdr) You might also make \topmargin smaller to compensate: - Warning: (fancyhdr) \addtolength{\topmargin}{-3.60004pt}. - --- finished re-building ‘Vig02-handling-metadata-and-annotations.Rmd’ - - SUMMARY: processing the following file failed: - ‘Vig01b-introduction-to-alpsnmr-old-api.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # aroma.core
@@ -433,47 +351,6 @@ Run `revdep_details(, "ChromSCape")` for more info prepare_Rd: raw_counts_to_sparse_matrix.Rd:6-8: Dropping empty section \source ``` -# civis - -
- -* Version: 3.1.1 -* GitHub: https://github.com/civisanalytics/civis-r -* Source code: https://github.com/cran/civis -* Date/Publication: 2023-02-28 08:02:29 UTC -* Number of recursive dependencies: 88 - -Run `revdep_details(, "civis")` for more info - -
- -## Newly broken - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(civis) - > - > test_check("civis") - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 1058 ] - - ... - Backtrace: - ▆ - 1. ├─civis::cancel(fut) - 2. └─civis:::cancel.CivisFuture(fut) - 3. ├─base::`$<-`(`*tmp*`, "state", value = ``) - 4. └─future:::`$<-.Future`(`*tmp*`, "state", value = ``) - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 1058 ] - Error: Test failures - Execution halted - ``` - # codebook
@@ -490,31 +367,6 @@ Run `revdep_details(, "codebook")` for more info ## In both -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘codebook.Rmd’ using rmarkdown - Failed with error: 'there is no package called 'GGally'' - Failed with error: 'there is no package called 'GGally'' - Failed with error: 'there is no package called 'GGally'' - Failed with error: 'there is no package called 'GGally'' - Quitting from lines 85-86 (codebook.Rmd) - Error: processing vignette 'codebook.Rmd' failed with diagnostics: - UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". - --- failed re-building ‘codebook.Rmd’ - ... - Failed with error: 'there is no package called 'GGally'' - Failed with error: 'there is no package called 'GGally'' - Failed with error: 'there is no package called 'GGally'' - --- finished re-building ‘codebook_tutorial.Rmd’ - - SUMMARY: processing the following file failed: - ‘codebook.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - * checking package dependencies ... NOTE ``` Package suggested but not available for checking: ‘userfriendlyscience’ @@ -548,31 +400,6 @@ Run `revdep_details(, "cSEM")` for more info ## In both -* checking examples ... ERROR - ``` - Running examples in ‘cSEM-Ex.R’ failed - The error most likely occurred in: - - > ### Name: resampleData - > ### Title: Resample data - > ### Aliases: resampleData - > - > ### ** Examples - > - > # =========================================================================== - ... - Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : - data length is not a multiple of split variable - Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : - data length is not a multiple of split variable - Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : - data length is not a multiple of split variable - Warning in split.default(x = seq_len(nrow(x)), f = f, drop = drop, ...) : - data length is not a multiple of split variable - Error: UNRELIABLE VALUE: One of the ‘future.apply’ iterations (‘future_lapply-1’) unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". - Execution halted - ``` - * checking dependencies in R code ... NOTE ``` Namespace in Imports field not imported from: ‘Rdpack’ @@ -623,6 +450,47 @@ Run `revdep_details(, "DeclareDesign")` for more info Package suggested but not available for checking: ‘DesignLibrary’ ``` +# dhReg + +
+ +* Version: 0.1.1 +* GitHub: NA +* Source code: https://github.com/cran/dhReg +* Date/Publication: 2021-02-28 12:30:02 UTC +* Number of recursive dependencies: 68 + +Run `revdep_details(, "dhReg")` for more info + +
+ +## Newly broken + +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # install.packages("testthat") + > library(testthat) + > # install.packages("forecast") + > # library(forecast) + > # install.packages("stats") + > # library(stats) + ... + 1. dhReg::dhr(...) + 2. future::plan(future::multiprocess) + 3. future (local) plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) + 4. future (local) warn_about_multiprocess(newStack) + 5. future (local) warn_about_deprecated(stack, strategy = "multiprocess", fmtstr = sprintf("Strategy '%%s' is %%s in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.")) + 6. base (local) dfcn(msg = msg, package = .packageName) + + Error in reporter$stop_if_needed() : Test failed + Calls: test_that -> + Execution halted + ``` + # dipsaus
@@ -848,6 +716,47 @@ Run `revdep_details(, "fect")` for more info All declared Imports should be used. ``` +# fiery + +
+ +* Version: 1.1.4 +* GitHub: https://github.com/thomasp85/fiery +* Source code: https://github.com/cran/fiery +* Date/Publication: 2022-08-16 07:20:06 UTC +* Number of recursive dependencies: 74 + +Run `revdep_details(, "fiery")` for more info + +
+ +## Newly broken + +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(fiery) + > + > test_check("fiery") + + [ FAIL 1 | WARN 0 | SKIP 1 | PASS 253 ] + ... + 2. └─private$ASYNC$add(substitute(expr), then, substituted = TRUE) + 3. └─private$make_future(expr, then, ...) + 4. ├─base::do.call(private$catcher, list(expr = expr, lazy = private$lazy)) + 5. └─future::multiprocess(...) + 6. └─future (local) dfcn(msg = msg, package = .packageName) + 7. └─base::.Defunct(...) + + [ FAIL 1 | WARN 0 | SKIP 1 | PASS 253 ] + Error: Test failures + Execution halted + ``` + # flowGraph
@@ -923,47 +832,6 @@ Run `revdep_details(, "forecastML")` for more info All declared Imports should be used. ``` -# future.tests - -
- -* Version: 0.5.0 -* GitHub: https://github.com/HenrikBengtsson/future.tests -* Source code: https://github.com/cran/future.tests -* Date/Publication: 2022-12-16 08:20:02 UTC -* Number of recursive dependencies: 15 - -Run `revdep_details(, "future.tests")` for more info - -
- -## Newly broken - -* checking tests ... - ``` - Running ‘Test-class.R’ - Running ‘check.R’ - ERROR - Running the tests in ‘tests/check.R’ failed. - Last 50 lines of output: - [[1]][[51]][[1]] - TestResult: - - Test: - - Title: 'value() - visibility' - - Tags: 'value', 'visibility' - ... - - args: function (..., envir = parent.frame()) - - tweaked: FALSE - - call: plan(sequential) - - attr(,"exit_code") - [1] 1 - Total number of errors: 1 - > proc.time() - user system elapsed - 5.376 0.434 14.418 - ``` - # geocmeans
@@ -980,31 +848,6 @@ Run `revdep_details(, "geocmeans")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - |======================================================================| 100%[1] "Calculating the Jaccard values..." - [1] "Extracting the centres of the clusters..." - [1] "Standardizing the data (set parameter to FALSE to avoid this step)" - - | - | | 0% - ... - 8. │ ├─future::resolve(...) - 9. │ └─future:::resolve.list(...) - 10. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) - 11. │ └─future:::signalConditions(...) - 12. │ └─base::stop(condition) - 13. └─future.apply (local) ``(``) - - [ FAIL 1 | WARN 5 | SKIP 0 | PASS 40 ] - Error: Test failures - Execution halted - ``` - * checking installed package size ... NOTE ``` installed size is 14.5Mb @@ -1109,45 +952,6 @@ Run `revdep_details(, "gsynth")` for more info libs 4.9Mb ``` -# gtfs2emis - -
- -* Version: 0.1.0 -* GitHub: https://github.com/ipeaGIT/gtfs2emis -* Source code: https://github.com/cran/gtfs2emis -* Date/Publication: 2022-11-14 11:30:05 UTC -* Number of recursive dependencies: 96 - -Run `revdep_details(, "gtfs2emis")` for more info - -
- -## In both - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘gtfs2emis_emission_factor.Rmd’ using rmarkdown - --- finished re-building ‘gtfs2emis_emission_factor.Rmd’ - - --- re-building ‘gtfs2emis_fleet_data.Rmd’ using rmarkdown - --- finished re-building ‘gtfs2emis_fleet_data.Rmd’ - - --- re-building ‘gtfs2emis_intro_vignette.Rmd’ using rmarkdown - Quitting from lines 119-130 (gtfs2emis_intro_vignette.Rmd) - Error: processing vignette 'gtfs2emis_intro_vignette.Rmd' failed with diagnostics: - UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". - --- failed re-building ‘gtfs2emis_intro_vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘gtfs2emis_intro_vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # gWQS
@@ -1533,67 +1337,6 @@ Run `revdep_details(, "keyATM")` for more info libs 23.6Mb ``` -# lava - -
- -* Version: 1.7.2.1 -* GitHub: https://github.com/kkholst/lava -* Source code: https://github.com/cran/lava -* Date/Publication: 2023-02-27 08:12:30 UTC -* Number of recursive dependencies: 136 - -Run `revdep_details(, "lava")` for more info - -
- -## In both - -* checking tests ... - ``` - Running ‘test-all.R’ - ERROR - Running the tests in ‘tests/test-all.R’ failed. - Last 50 lines of output: - > #library("lava") - > suppressPackageStartupMessages(library("testthat")) - > test_check("lava") - Loading required package: lava - - Attaching package: 'lava' - ... - 10. │ ├─future::resolve(...) - 11. │ └─future:::resolve.list(...) - 12. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) - 13. │ └─future:::signalConditions(...) - 14. │ └─base::stop(condition) - 15. └─future.apply (local) ``(``) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 254 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘correlation.Rmd’ using rmarkdown - Quitting from lines 250-253 (correlation.Rmd) - Error: processing vignette 'correlation.Rmd' failed with diagnostics: - UNRELIABLE VALUE: One of the 'future.apply' iterations ('future_lapply-1') unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". - --- failed re-building ‘correlation.Rmd’ - - --- re-building ‘nonlinear.Rmd’ using rmarkdown - --- finished re-building ‘nonlinear.Rmd’ - - SUMMARY: processing the following file failed: - ‘correlation.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # lidR
@@ -1637,7 +1380,7 @@ Run `revdep_details(, "lidR")` for more info * checking tests ... ``` - Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 37779 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + Running ‘testthat.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 9093 Aborted ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 ERROR Running the tests in ‘tests/testthat.R’ failed. @@ -1814,6 +1557,33 @@ Run `revdep_details(, "MineICA")` for more info
+## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘MineICA-Ex.R’ failed + The error most likely occurred in: + + > ### Name: clusterFastICARuns + > ### Title: Run of fastICA and JADE algorithms + > ### Aliases: clusterFastICARuns + > + > ### ** Examples + > + > ## generate a data + ... + > ## Random initializations are used for each iteration of FastICA + > ## Estimates are clustered using hierarchical clustering with average linkage + > res <- clusterFastICARuns(X=M, nbComp=2, alg.type="deflation", + + nbIt=3, funClus="hclust", method="average") + FastICA iteration 1 + Warning: executing %dopar% sequentially: no parallel backend registered + FastICA iteration 2 + FastICA iteration 3 + Error: Strategy 'multiprocess' is defunct in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'. + Execution halted + ``` + ## In both * checking running R code from vignettes ... @@ -1823,15 +1593,15 @@ Run `revdep_details(, "MineICA")` for more info Errors in running code in vignettes: when running code in ‘MineICA.Rnw’ ... - [25] "hgu133aPFAM" "hgu133aPMID" "hgu133aPMID2PROBE" - [28] "hgu133aPROSITE" "hgu133aREFSEQ" "hgu133aSYMBOL" - [31] "hgu133aUNIPROT" "hgu133a_dbInfo" "hgu133a_dbconn" - [34] "hgu133a_dbfile" "hgu133a_dbschema" + > resPath(params) + [1] "mainz/" - > mart <- useMart(biomart = "ensembl", dataset = "hsapiens_gene_ensembl") + > resW <- writeProjByComp(icaSet = icaSetMainz, params = params, + + mart = mart, level = "genes", selCutoffWrite = 2.5) When sourcing ‘MineICA.R’: - Error: Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 365789 out of -1 bytes received + Error: task 2 failed - "Multiple cache results found. + Please clear your cache by running biomartCacheClear()" Execution halted ``` @@ -1943,8 +1713,8 @@ Run `revdep_details(, "MineICA")` for more info IQR, mad, sd, var, xtabs ... - Error in { : task 2 failed - "Multiple cache results found. - Please clear your cache by running biomartCacheClear()" + Error in curl::curl_fetch_memory(url, handle = handle) : + Timeout was reached: [www.ensembl.org:443] Operation timed out after 10000 milliseconds with 0 out of -1 bytes received --- failed re-building ‘MineICA.Rnw’ @@ -1994,31 +1764,6 @@ Run `revdep_details(, "mistyR")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - Generating paraview using 2 nearest neighbors per unit - - Generating paraview - - Generating paraview - [ FAIL 2 | WARN 74 | SKIP 0 | PASS 168 ] - ... - 27. └─rlang::abort(...) - ── Failure ('test-misty.R:212'): k for cv , n.bags for bagging can be changed and approx works ── - first.run < second.run is not TRUE - - `actual`: FALSE - `expected`: TRUE - - [ FAIL 2 | WARN 74 | SKIP 0 | PASS 168 ] - Error: Test failures - Execution halted - ``` - * checking R code for possible problems ... NOTE ``` aggregate_results: no visible binding for global variable ‘.data’ @@ -2146,48 +1891,6 @@ Run `revdep_details(, "OOS")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(OOS) - > - > test_check("OOS") - Error : UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". - Error : UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". - ... - Backtrace: - ▆ - 1. ├─testthat::expect_true(...) at test-forecast_multivariate.R:76:2 - 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. └─base::is.data.frame(forecast.multi$forecasts) - - [ FAIL 3 | WARN 1004 | SKIP 0 | PASS 26 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘basic_introduction.Rmd’ using rmarkdown - Quitting from lines 68-78 (basic_introduction.Rmd) - Error: processing vignette 'basic_introduction.Rmd' failed with diagnostics: - UNRELIABLE VALUE: Future ('') unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". - --- failed re-building ‘basic_introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘basic_introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - * checking LazyData ... NOTE ``` 'LazyData' is specified without a 'data' directory @@ -2287,45 +1990,6 @@ Run `revdep_details(, "phylolm")` for more info Packages unavailable to check Rd xrefs: ‘geiger’, ‘caper’ ``` -# PINstimation - -
- -* Version: 0.1.1 -* GitHub: https://github.com/monty-se/PINstimation -* Source code: https://github.com/cran/PINstimation -* Date/Publication: 2022-10-18 22:58:01 UTC -* Number of recursive dependencies: 65 - -Run `revdep_details(, "PINstimation")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘PINstimation.rmd’ using rmarkdown - Quitting from lines 255-256 (PINstimation.rmd) - Error: processing vignette 'PINstimation.rmd' failed with diagnostics: - Future () added variables to the global environment. A future expression should never assign variables to the global environment - neither by assign() nor by <<-: [n=1] '.lwbound' - --- failed re-building ‘PINstimation.rmd’ - - --- re-building ‘parallel_processing.rmd’ using rmarkdown - Quitting from lines 81-84 (parallel_processing.rmd) - Error: processing vignette 'parallel_processing.rmd' failed with diagnostics: - Future () added variables to the global environment. A future expression should never assign variables to the global environment - neither by assign() nor by <<-: [n=1] '.lwbound' - --- failed re-building ‘parallel_processing.rmd’ - - SUMMARY: processing the following files failed: - ‘PINstimation.rmd’ ‘parallel_processing.rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # PLNmodels
@@ -2441,7 +2105,32 @@ Run `revdep_details(, "prewas")` for more info
-## In both +## Newly broken + +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Last 50 lines of output: + 3. └─future (local) plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) + 4. └─future (local) warn_about_multiprocess(newStack) + 5. └─future (local) warn_about_deprecated(stack, strategy = "multiprocess", fmtstr = sprintf("Strategy '%%s' is %%s in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.")) + 6. └─base (local) dfcn(msg = msg, package = .packageName) + ── Error ('test-reference_alleles.R:89'): remove_unknown_alleles correctly removes Ns when given valid input ── + + ... + 1. └─prewas:::get_ancestral_alleles(tree = temp_tree, mat = temp_dna_list$variant_only_dna_mat) at test-reference_alleles.R:258:2 + 2. └─future::plan(future::multiprocess) + 3. └─future (local) plan_set(newStack, skip = .skip, cleanup = .cleanup, init = .init) + 4. └─future (local) warn_about_multiprocess(newStack) + 5. └─future (local) warn_about_deprecated(stack, strategy = "multiprocess", fmtstr = sprintf("Strategy '%%s' is %%s in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.")) + 6. └─base (local) dfcn(msg = msg, package = .packageName) + + [ FAIL 6 | WARN 0 | SKIP 0 | PASS 312 ] + Error: Test failures + Execution halted + ``` * checking re-building of vignette outputs ... ERROR ``` @@ -2450,7 +2139,7 @@ Run `revdep_details(, "prewas")` for more info --- re-building ‘getting_started_with_prewas.Rmd’ using rmarkdown Quitting from lines 136-141 (getting_started_with_prewas.Rmd) Error: processing vignette 'getting_started_with_prewas.Rmd' failed with diagnostics: - UNRELIABLE VALUE: One of the 'future.apply' iterations ('future_apply-1') unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". + Strategy 'multiprocess' is defunct in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'. --- failed re-building ‘getting_started_with_prewas.Rmd’ SUMMARY: processing the following file failed: @@ -2460,6 +2149,8 @@ Run `revdep_details(, "prewas")` for more info Execution halted ``` +## In both + * checking dependencies in R code ... NOTE ``` Namespace in Imports field not imported from: ‘stats’ @@ -2572,6 +2263,47 @@ Run `revdep_details(, "RAINBOWR")` for more info libs 36.5Mb ``` +# rangeMapper + +
+ +* Version: 2.0.3 +* GitHub: https://github.com/mpio-be/rangeMapper +* Source code: https://github.com/cran/rangeMapper +* Date/Publication: 2022-10-03 22:20:02 UTC +* Number of recursive dependencies: 113 + +Run `revdep_details(, "rangeMapper")` for more info + +
+ +## In both + +* checking tests ... + ``` + Running ‘testthat.R’ + ERROR + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(rangeMapper) + rangeMapper 2.0.3 + > + > test_check("rangeMapper") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 58 ] + ... + 24. │ └─terra:::error(f, x@ptr$getError()) + 25. │ └─base::stop("[", f, "] ", emsg, ..., call. = FALSE) + 26. └─base::.handleSimpleError(``, "[rast] empty srs", base::quote(NULL)) + 27. └─base (local) h(simpleError(msg, call)) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 58 ] + Error: Test failures + In addition: Warning message: + call dbDisconnect() when finished working with a connection + Execution halted + ``` + # regmedint
@@ -2612,16 +2344,16 @@ Run `revdep_details(, "reproducible")` for more info * checking tests ... ``` - Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 72596 Segmentation fault ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 + Running ‘test-all.R’/software/c4/cbi/software/R-4.2.2-gcc10/lib64/R/bin/BATCH: line 60: 72435 Segmentation fault ${R_HOME}/bin/R -f ${in} ${opts} ${R_BATCH_OPTIONS} > ${out} 2>&1 ERROR Running the tests in ‘tests/test-all.R’ failed. Last 50 lines of output: - adding: scratch/henrik/1184987/Rtmpoj91ji/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) - adding: scratch/henrik/1184987/Rtmpoj91ji/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) + adding: scratch/henrik/1187620/RtmpLUtHcR/reproducible/4sZYfp_038/1Gis54o.tif (stored 0%) + adding: scratch/henrik/1187620/RtmpLUtHcR/reproducible/4sZYfp_038/EiHkghZ.grd (stored 0%) *** caught segfault *** - address 0x40, cause 'memory not mapped' + address 0x8, cause 'memory not mapped' ... 36: doTryCatch(return(expr), name, parentenv, handler) 37: tryCatchOne(expr, names, parentenv, handlers[[1L]]) @@ -2811,47 +2543,6 @@ Run `revdep_details(, "sdmTMB")` for more info Package unavailable to check Rd xrefs: ‘INLA’ ``` -# semtree - -
- -* Version: 0.9.18 -* GitHub: NA -* Source code: https://github.com/cran/semtree -* Date/Publication: 2022-05-13 20:20:02 UTC -* Number of recursive dependencies: 105 - -Run `revdep_details(, "semtree")` for more info - -
- -## Newly broken - -* checking tests ... - ``` - Running ‘invariance.R’ - Running ‘lavaan.R’ - Running ‘tree.R’ - Running ‘vim.R’ - ERROR - Running the tests in ‘tests/vim.R’ failed. - Last 50 lines of output: - + to=manifests, - + arrows=1, - + free=FALSE, - ... - Start values from best fit: - 0.0517425665515153,0.0579964396186258,0.0467583826565627,0.0520836944320659,0.0361130740992484,2.41004055880336,0.477157334656551,0.973042342886596,3.49639424861343,-0.465977367752192 - ✖ Variable noise is numeric but has only few unique values. Consider recoding as ordered factor. - ✔ Tree construction finished [took 6s]. - ✖ Variable noise is numeric but has only few unique values. Consider recoding as ordered factor. - ✔ Tree construction finished [took 6s]. - ✖ Variable noise is numeric but has only few unique values. Consider recoding as ordered factor. - ✔ Tree construction finished [took 5s]. - Error: Future (future_mapply-1) added variables to the global environment. A future expression should never assign variables to the global environment - neither by assign() nor by <<-: [n=1] 'global.node.id' - Execution halted - ``` - # sentopics
@@ -3080,45 +2771,6 @@ Run `revdep_details(, "SimDesign")` for more info doc 6.2Mb ``` -# simhelpers - -
- -* Version: 0.1.2 -* GitHub: https://github.com/meghapsimatrix/simhelpers -* Source code: https://github.com/cran/simhelpers -* Date/Publication: 2022-05-03 22:40:02 UTC -* Number of recursive dependencies: 103 - -Run `revdep_details(, "simhelpers")` for more info - -
- -## In both - -* checking examples ... ERROR - ``` - Running examples in ‘simhelpers-Ex.R’ failed - The error most likely occurred in: - - > ### Name: evaluate_by_row - > ### Title: Evaluate a simulation function on each row of a data frame or - > ### tibble - > ### Aliases: evaluate_by_row - > - > ### ** Examples - > - > df <- data.frame( - + n = 3:5, - + lambda = seq(8, 16, 4) - + ) - > - > evaluate_by_row(df, rpois) - Error: UNRELIABLE VALUE: Future (‘’) unexpectedly generated random numbers without specifying argument 'seed'. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'seed=NULL', or set option 'future.rng.onMisuse' to "ignore". - Timing stopped at: 0.227 0.035 0.614 - Execution halted - ``` - # skpr
@@ -3237,56 +2889,6 @@ Run `revdep_details(, "SPARSEMODr")` for more info ## In both -* checking examples ... ERROR - ``` - Running examples in ‘SPARSEMODr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: model_parallel - > ### Title: Parallelized implementation of the SPARSE-MOD models - > ### Aliases: model_parallel - > - > ### ** Examples - > - > ## See vignettes for more detailed work-ups. - ... - Parameter input_R_pops was not specified; assuming to be zeroes. - Parameter input_D_pops was not specified; assuming to be zeroes. - > - > covid_model_output <- - + get_result( - + input_realz_seeds = realz_seeds, - + control = covid19_control - + ) - Error: UNRELIABLE VALUE: One of the ‘future.apply’ iterations (‘future_lapply-1’) unexpectedly generated random numbers without declaring so. There is a risk that those random numbers are not statistically sound and the overall results might be invalid. To fix this, specify 'future.seed=TRUE'. This ensures that proper, parallel-safe random numbers are produced via the L'Ecuyer-CMRG method. To disable this check, use 'future.seed = NULL', or set option 'future.rng.onMisuse' to "ignore". - Execution halted - ``` - -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > if(require(testthat))test_check("SPARSEMODr") - Loading required package: testthat - Loading required package: SPARSEMODr - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 13. │ ├─future::resolve(...) - 14. │ └─future:::resolve.list(...) - 15. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) - 16. │ └─future:::signalConditions(...) - 17. │ └─base::stop(condition) - 18. └─future.apply (local) ``(``) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - * checking dependencies in R code ... NOTE ``` Namespaces in Imports field not imported from: @@ -3392,31 +2994,6 @@ Run `revdep_details(, "spNetwork")` for more info ## In both -* checking tests ... - ``` - Running ‘testthat.R’ - ERROR - Running the tests in ‘tests/testthat.R’ failed. - Last 50 lines of output: - 5. │ ├─base::withCallingHandlers(...) - 6. │ └─(function() {... - 7. │ ├─future::value(fs) - 8. │ └─future:::value.list(fs) - 9. │ ├─future::resolve(...) - 10. │ └─future:::resolve.list(...) - ... - 9. │ ├─future::resolve(...) - 10. │ └─future:::resolve.list(...) - 11. │ └─future (local) signalConditionsASAP(obj, resignal = FALSE, pos = ii) - 12. │ └─future:::signalConditions(...) - 13. │ └─base::stop(condition) - 14. └─future.apply (local) ``(``) - - [ FAIL 5 | WARN 3 | SKIP 0 | PASS 68 ] - Error: Test failures - Execution halted - ``` - * checking installed package size ... NOTE ``` installed size is 25.2Mb diff --git a/tests/multiprocess.R b/tests/multiprocess.R deleted file mode 100644 index d30d1f6e..00000000 --- a/tests/multiprocess.R +++ /dev/null @@ -1,149 +0,0 @@ -source("incl/start.R") -library("listenv") -plan(multiprocess) - -message("*** multiprocess() ...") - -for (cores in 1:availCores) { - ## Speed up CRAN checks: Skip on CRAN Windows 32-bit - if (!fullTest && isWin32) next - - message(sprintf("Testing with %d cores ...", cores)) - options(mc.cores = cores) - - ## No global variables - f <- multiprocess({ - 42L - }) - print(f) - stopifnot(inherits(f, "SequentialFuture")) - - print(resolved(f)) - y <- value(f) - print(y) - stopifnot(y == 42L) - - - ## A global variable - a <- 0 - f <- multiprocess({ - b <- 3 - c <- 2 - a * b * c - }) - print(f) - - - ## A multiprocess future is evaluated in a separate - ## R process. Changing the value of a global - ## variable should not affect the result of the - ## future. - a <- 7 ## Make sure globals are frozen - v <- value(f) - print(v) - stopifnot(v == 0) - - - message("*** multiprocess() with globals and blocking") - x <- listenv() - for (ii in 1:4) { - message(sprintf(" - Creating multiprocess future #%d ...", ii)) - x[[ii]] <- multiprocess({ ii }, globals = TRUE) - } - message(sprintf(" - Resolving %d multiprocess futures", length(x))) - v <- sapply(x, FUN = value) - stopifnot(all(v == 1:4)) - - - message("*** multiprocess() and errors") - f <- multiprocess({ - stop("Whoops!") - 1 - }) - print(f) - v <- value(f, signal = FALSE) - print(v) - stopifnot(inherits(v, "simpleError")) - - res <- try(value(f), silent = TRUE) - print(res) - stopifnot(inherits(res, "try-error")) - - ## Error is repeated - res <- try(value(f), silent = TRUE) - print(res) - stopifnot(inherits(res, "try-error")) - - ## Custom error class - f <- multiprocess({ - stop(structure(list(message = "boom"), - class = c("MyError", "error", "condition"))) - }) - print(f) - v <- value(f, signal = FALSE) - print(v) - stopifnot(inherits(v, "error"), inherits(v, "MyError")) - - ## Make sure error is signaled - res <- tryCatch(value(f), error = identity) - stopifnot(inherits(res, "error"), inherits(res, "MyError")) - - message("*** multiprocess() - too large globals ...") - ooptsT <- options(future.globals.maxSize = object.size(1:1014)) - - limit <- getOption("future.globals.maxSize") - cat(sprintf("Max total size of globals: %g bytes\n", limit)) - - for (workers in unique(c(1L, availableCores()))) { - message("Max number of processes: ", workers) - - ## A large object - a <- 1:1014 - yTruth <- sum(a) - size <- object.size(a) - cat(sprintf("a: %g bytes\n", size)) - f <- multiprocess({ sum(a) }, globals = TRUE, workers = workers) - print(f) - rm(list = "a") - v <- value(f) - print(v) - stopifnot(v == yTruth) - - - ## A too large object - a <- 1:1019 ## also on 32-bit platforms - yTruth <- sum(a) - size <- object.size(a) - cat(sprintf("a: %g bytes\n", size)) - res <- try(f <- multiprocess({ sum(a) }, globals = TRUE, workers = workers), silent = TRUE) - rm(list = "a") - stopifnot(inherits(res, "try-error")) - } - - ## Undo options changed in this test - options(ooptsT) - - message("*** multiprocess() - too large globals ... DONE") - - - message("*** multiprocess(..., workers = 1L) ...") - - a <- 2 - b <- 3 - yTruth <- a * b - - f <- multiprocess({ a * b }, globals = TRUE, workers = 1L) - rm(list = c("a", "b")) - - v <- value(f) - print(v) - stopifnot(v == yTruth) - - message("*** multiprocess(..., workers = 1L) ... DONE") - - message(sprintf("Testing with %d cores ... DONE", cores)) -} ## for (cores ...) - -message("*** multiprocess() ... DONE") - -source("incl/end.R") From b1d1271412c32bedb13f059bce31ad906dbb6dff Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Mon, 6 Mar 2023 19:01:11 +0100 Subject: [PATCH 87/88] Decide to defunct 'multiprocess' for the next release [#546] --- NEWS.md | 8 +-- R/multiprocess.R | 7 +- R/options.R | 2 +- R/zzz.plan.R | 12 +--- man/plan.Rd | 10 --- tests/multiprocess.R | 149 ------------------------------------------- 6 files changed, 9 insertions(+), 179 deletions(-) delete mode 100644 tests/multiprocess.R diff --git a/NEWS.md b/NEWS.md index 355b638d..cde50dc7 100644 --- a/NEWS.md +++ b/NEWS.md @@ -22,12 +22,12 @@ ## Deprecated and Defunct + * The 'multiprocess' strategy, which has been deprecated since future + 1.20.0 [2020-10-30] is now defunct. Please use 'multisession' + (recommended) or 'multicore' instead. + * Add optional assertion of the internal Future `state` field. - * Deprecated `plan(multiprocess, ...)` is now defunct when running in - interactive mode. The next step is to make it defunct also when - running in batch mode. - # Version 1.31.0 [2023-01-31] diff --git a/R/multiprocess.R b/R/multiprocess.R index 16e81606..65118b3a 100644 --- a/R/multiprocess.R +++ b/R/multiprocess.R @@ -23,17 +23,16 @@ #' @export multiprocess <- function(..., workers = availableCores(), envir = parent.frame()) { - msg1 <- "Detected creation of a 'multiprocess' future. Strategy 'multiprocess' is deprecated in future (>= 1.20.0) [2020-10-30]." - msg2 <- "Instead, specify either 'multisession' (recommended) or 'multicore'." + msg <- "Detected creation of a 'multiprocess' future, which are defunct in future (>= 1.32.0) [2023-03-06]." + msg <- paste(msg, "Instead, specify either 'multisession' (recommended) or 'multicore'.") defunct <- getOption("future.deprecated.defunct") if (is.element("multiprocess", defunct)) { - msg <- paste(msg1, "It will soon become defunct, i.e. produce an error.", msg2) ## Need to wrap .Defunct() in another frame to avoid: ## Error in as.vector(x, "character") : ## cannot coerce type 'closure' to vector of type 'character' dfcn <- function(...) .Defunct(...) } else { - msg <- paste(msg1, msg2, "Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.") + msg <- paste(msg, "If still used, 'multiprocess' becomes the same as 'sequential'.") dfcn <- .Deprecated } dfcn(msg = msg, package = .packageName) diff --git a/R/options.R b/R/options.R index 393f08dc..b3f8642e 100644 --- a/R/options.R +++ b/R/options.R @@ -274,7 +274,7 @@ update_package_options <- function(debug = FALSE) { update_package_option("future.deprecated.ignore", split = ",", debug = debug) - update_package_option("future.deprecated.defunct", mode = "character", split = ",", default = if (interactive()) "multiprocess" else NULL, debug = debug) + update_package_option("future.deprecated.defunct", mode = "character", split = ",", default = "multiprocess", debug = debug) update_package_option("future.fork.multithreading.enable", mode = "logical", debug = debug) diff --git a/R/zzz.plan.R b/R/zzz.plan.R index b573d472..5f6e1ad1 100644 --- a/R/zzz.plan.R +++ b/R/zzz.plan.R @@ -75,16 +75,6 @@ #' are available on high-performance compute (HPC) clusters, e.g. LSF, #' Slurm, TORQUE/PBS, Sun Grid Engine, and OpenLava. #' -#' The following future strategies are _deprecated_ and must not be used: -#' -#' \itemize{ -#' \item{[`multiprocess`]:}{(DEPRECATED since future 1.20.0) -#' If multicore evaluation is supported, that will be used, -#' otherwise multisession evaluation will be used. -#' _Please use `multisession`, or possibly `multicore` instead._ -#' } -#' } -#' #' To "close" any background workers (e.g. `multisession`), change #' the plan to something different; `plan(sequential)` is recommended #' for this. @@ -187,7 +177,7 @@ plan <- local({ } warn_about_multiprocess <- function(stack) { - warn_about_deprecated(stack, strategy = "multiprocess", fmtstr = sprintf("Strategy '%%s' is %%s in future (>= 1.20.0) [2020-10-30]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'. Starting with future 1.31.0 [2023-01-31], 'multiprocess' is the same as 'sequential'.")) + warn_about_deprecated(stack, strategy = "multiprocess", fmtstr = sprintf("Strategy '%%s' is %%s in future (>= 1.32.0) [2023-03-06]. Instead, explicitly specify either 'multisession' (recommended) or 'multicore'.")) } warn_about_remote <- function(stack) { diff --git a/man/plan.Rd b/man/plan.Rd index 4d469a8e..e55d9504 100644 --- a/man/plan.Rd +++ b/man/plan.Rd @@ -91,16 +91,6 @@ These types of futures are resolved via job schedulers, which typically are available on high-performance compute (HPC) clusters, e.g. LSF, Slurm, TORQUE/PBS, Sun Grid Engine, and OpenLava. -The following future strategies are \emph{deprecated} and must not be used: - -\itemize{ -\item{\code{\link{multiprocess}}:}{(DEPRECATED since future 1.20.0) -If multicore evaluation is supported, that will be used, -otherwise multisession evaluation will be used. -\emph{Please use \code{multisession}, or possibly \code{multicore} instead.} -} -} - To "close" any background workers (e.g. \code{multisession}), change the plan to something different; \code{plan(sequential)} is recommended for this. diff --git a/tests/multiprocess.R b/tests/multiprocess.R deleted file mode 100644 index d30d1f6e..00000000 --- a/tests/multiprocess.R +++ /dev/null @@ -1,149 +0,0 @@ -source("incl/start.R") -library("listenv") -plan(multiprocess) - -message("*** multiprocess() ...") - -for (cores in 1:availCores) { - ## Speed up CRAN checks: Skip on CRAN Windows 32-bit - if (!fullTest && isWin32) next - - message(sprintf("Testing with %d cores ...", cores)) - options(mc.cores = cores) - - ## No global variables - f <- multiprocess({ - 42L - }) - print(f) - stopifnot(inherits(f, "SequentialFuture")) - - print(resolved(f)) - y <- value(f) - print(y) - stopifnot(y == 42L) - - - ## A global variable - a <- 0 - f <- multiprocess({ - b <- 3 - c <- 2 - a * b * c - }) - print(f) - - - ## A multiprocess future is evaluated in a separate - ## R process. Changing the value of a global - ## variable should not affect the result of the - ## future. - a <- 7 ## Make sure globals are frozen - v <- value(f) - print(v) - stopifnot(v == 0) - - - message("*** multiprocess() with globals and blocking") - x <- listenv() - for (ii in 1:4) { - message(sprintf(" - Creating multiprocess future #%d ...", ii)) - x[[ii]] <- multiprocess({ ii }, globals = TRUE) - } - message(sprintf(" - Resolving %d multiprocess futures", length(x))) - v <- sapply(x, FUN = value) - stopifnot(all(v == 1:4)) - - - message("*** multiprocess() and errors") - f <- multiprocess({ - stop("Whoops!") - 1 - }) - print(f) - v <- value(f, signal = FALSE) - print(v) - stopifnot(inherits(v, "simpleError")) - - res <- try(value(f), silent = TRUE) - print(res) - stopifnot(inherits(res, "try-error")) - - ## Error is repeated - res <- try(value(f), silent = TRUE) - print(res) - stopifnot(inherits(res, "try-error")) - - ## Custom error class - f <- multiprocess({ - stop(structure(list(message = "boom"), - class = c("MyError", "error", "condition"))) - }) - print(f) - v <- value(f, signal = FALSE) - print(v) - stopifnot(inherits(v, "error"), inherits(v, "MyError")) - - ## Make sure error is signaled - res <- tryCatch(value(f), error = identity) - stopifnot(inherits(res, "error"), inherits(res, "MyError")) - - message("*** multiprocess() - too large globals ...") - ooptsT <- options(future.globals.maxSize = object.size(1:1014)) - - limit <- getOption("future.globals.maxSize") - cat(sprintf("Max total size of globals: %g bytes\n", limit)) - - for (workers in unique(c(1L, availableCores()))) { - message("Max number of processes: ", workers) - - ## A large object - a <- 1:1014 - yTruth <- sum(a) - size <- object.size(a) - cat(sprintf("a: %g bytes\n", size)) - f <- multiprocess({ sum(a) }, globals = TRUE, workers = workers) - print(f) - rm(list = "a") - v <- value(f) - print(v) - stopifnot(v == yTruth) - - - ## A too large object - a <- 1:1019 ## also on 32-bit platforms - yTruth <- sum(a) - size <- object.size(a) - cat(sprintf("a: %g bytes\n", size)) - res <- try(f <- multiprocess({ sum(a) }, globals = TRUE, workers = workers), silent = TRUE) - rm(list = "a") - stopifnot(inherits(res, "try-error")) - } - - ## Undo options changed in this test - options(ooptsT) - - message("*** multiprocess() - too large globals ... DONE") - - - message("*** multiprocess(..., workers = 1L) ...") - - a <- 2 - b <- 3 - yTruth <- a * b - - f <- multiprocess({ a * b }, globals = TRUE, workers = 1L) - rm(list = c("a", "b")) - - v <- value(f) - print(v) - stopifnot(v == yTruth) - - message("*** multiprocess(..., workers = 1L) ... DONE") - - message(sprintf("Testing with %d cores ... DONE", cores)) -} ## for (cores ...) - -message("*** multiprocess() ... DONE") - -source("incl/end.R") From a08b6f94d1137542ae89489cef323e6431bb3f59 Mon Sep 17 00:00:00 2001 From: Henrik Bengtsson Date: Tue, 7 Mar 2023 09:33:41 +0100 Subject: [PATCH 88/88] future 1.32.0 --- cran-comments.md | 26 ++++++++++++++++++++++++-- 1 file changed, 24 insertions(+), 2 deletions(-) diff --git a/cran-comments.md b/cran-comments.md index b55355ff..6b38ae43 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,12 +1,34 @@ # CRAN submission future 1.32.0 -on 2023-03-03 +on 2023-03-06 -I've verified this submission has no negative impact on any of the 280 reverse package dependencies available on CRAN (n = 261) and Bioconductor (n = 19). +I've checked this version towards 280 reverse package dependencies available on CRAN (n = 261) and Bioconductor (n = 19). This submission breaks three CRAN packages: dhReg, fiery, and prewas. This is because they use a function that has beeen deprecated since 2020 and their maintainers have been notified well in advance. dhReg and prewas have been reminded several times since 2021 and fiery since 2023-02-01. Thank you +## Resubmission 1 + +I'm resubmitting, because previous submission reported: + +> Flavor: r-devel-windows-x86_64 +> Check: for detritus in the temp directory, Result: NOTE +> Found the following files/directories: +> 'Rscript29dd03a4eb648' + +I suspect this is a false-positive due to some unknown hiccup. I cannot reproduce this elsewhere, including in win-builder. It was reported on win-builder neither prior to my previous submission nor after . + + +## Resubmission 2 + + + + +## Explanation on revdep errors + +This submission breaks three CRAN packages: dhReg, fiery, and prewas. This is because they use a now defunct function that has been deprecated since 2020. The maintainers have been notified well in advance. I have not received a response. Maintainers of dhReg and prewas have been reminded many times since 2021. The maintainer of fiery has been reminded twice since 2023-02-01. + + ## Notes not sent to CRAN ### R CMD check validation